Ambiguous types problem

Hello. Here I come with a question on type ambiguity. I typed it out in code to make it easier to follow and to paste it in your editor if you want to experiment with it.

It might seem silly, but now and then I find myself with these problems: for sure you can work around them (in this case by writing two functions), but it would be nice to know how to have the compiler accept those. Thanks in advance for any help!

{-# Language RankNTypes #-}
{-# Language AllowAmbiguousTypes #-}

module Prova where

-- Say I have a game, composed of 2 parts, the main story and a minigame.
data Story
data MiniGame
data Game = Game Index Story MiniGame
-- Index is for «which part is currently running now?»
data Index = IStory | IMiniGame

data Surface = Surface -- drawing surface

-- Both MainStory and Index are instances of a Play class
class Play s where
    draw :: s -> Surface -- what to blit
    quit :: s -> Bool    -- whether to exit
instance Play Story where
    -- …
instance Play MiniGame where
    -- …

-- gets a value using `Play` interface, depending on `Index`.
select :: Play s => Game -> (forall s. s -> a) -> a
select (Game i mag mig) f =
        case i of
          IStory -> f mag
          IMiniGame -> f mig
    -- I could write this function after turning AllowAmbiguousTypes on

-- -- but alas this test function — which simply fetches a bool depending
-- -- on Index — does not work.
-- test :: Game -> Bool
-- test g = select g quit

{-
prova.hs:34:10-22: error:
    • Ambiguous type variable ‘s0’ arising from a use of ‘select’
      prevents the constraint ‘(Play s0)’ from being solved.
      Probable fix: use a type annotation to specify what ‘s0’ should be.
      These potential instances exist:
        instance Play MiniGame -- Defined at prova.hs:21:10
        instance Play Story -- Defined at prova.hs:19:10
    • In the expression: select g quit
      In an equation for ‘test’: test g = select g quit
   |
34 | test g = select g quit
   |          ^^^^^^^^^^^^^
prova.hs:34:19-22: error:
    • No instance for (Play s) arising from a use of ‘quit’
      Possible fix:
        add (Play s) to the context of
          a type expected by the context:
            forall s. s -> Bool
    • In the second argument of ‘select’, namely ‘quit’
      In the expression: select g quit
      In an equation for ‘test’: test g = select g quit
   |
34 | test g = select g quit
   |                   ^^^^
-}

-- Is there a way to write a working select/test? I understand why
-- GHC does not fancy it but it seems one of those cases where I
-- should be able to tell the compiler «trust me on this one.»
-- ExistentialQuantification won’t cut it, as I would have to modify
-- Story and Minigame sooner or later in the logic cycle.

Do you perhaps want (forall s. Play s => s -> a) instead?

1 Like

Correct! But changing the sig to select :: Play s => Game -> (forall s. Play s => s -> a) -> a still leaves me with:

prova.hs:35:10: error:
    • Ambiguous type variable ‘s0’ arising from a use of ‘select’
      prevents the constraint ‘(Play s0)’ from being solved.
      Probable fix: use a type annotation to specify what ‘s0’ should be.
      These potential instances exist:
        instance Play MiniGame -- Defined at prova.hs:21:10
        instance Play Story -- Defined at prova.hs:19:10
    • In the expression: select g quit
      In an equation for ‘test’: test g = select g quit
   |
35 | test g = select g quit
   |          ^^^^^^^^^^^^^

I don’t think the initial typeclass constraint makes sense – you only want the one given under the quantification?

1 Like

Ah, indeed select :: Game -> (forall s. Play s => s -> a) -> a does it, many thanks!

Maybe we need warnings about shadowing type variables? Sounds like somthing that can be reported to github.com/haskell/error-messages or just to the GHC issue tracker.

Edit: The -Wname-shadowing already includes type variables, but warnings are suppressed when there are errors…

I guess it could be reported that the first s is unused (or only used in the Play s => constraint in a warning).

The best way to avoid this is to just avoid the AllowAmbiguousTypes extension, unless you are sure that you need it (I think GHC’s suggestion of that extension should be removed or should have a big warning attached to it).

3 Likes