Unexpected ambiguity in a seemingly valid Haskell 2010 program
wagnerdm at seas.upenn.edu
wagnerdm at seas.upenn.edu
Fri Nov 9 20:07:59 CET 2012
It's possible that the below blog post is related.
~d
http://hackage.haskell.org/trac/ghc/blog/LetGeneralisationInGhc7
Quoting Roman Cheplyaka <roma at ro-che.info>:
> For this module
>
> module Test where
>
> import System.Random
>
> data RPS = Rock | Paper | Scissors deriving (Show, Enum)
>
> instance Random RPS where
> random g =
> let (x, g') = randomR (0, 2) g
> in (toEnum x, g')
> randomR = undefined
>
> ghc (7.4.1 and 7.6.1) reports an error:
>
> rand.hs:9:9:
> No instance for (Random t0) arising from the ambiguity check for g'
> The type variable `t0' is ambiguous
> Possible fix: add a type signature that fixes these type variable(s)
> Note: there are several potential instances:
> instance Random RPS -- Defined at rand.hs:7:10
> instance Random Bool -- Defined in `System.Random'
> instance Random Foreign.C.Types.CChar -- Defined in `System.Random'
> ...plus 34 others
> When checking that g' has the inferred type `g'
> Probable cause: the inferred type is ambiguous
> In the expression: let (x, g') = randomR (0, 2) g in (toEnum x, g')
> In an equation for `random':
> random g = let (x, g') = randomR ... g in (toEnum x, g')
> Failed, modules loaded: none.
>
> There should be no ambiguity since 'toEnum' determines the type of x
> (Int), and that in turn fixes types of 0 and 2. Interestingly,
> annotating 0 or 2 with the type makes the problem go away.
>
> jhc 0.8.0 compiles this module fine.
>
> Roman
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
>
More information about the Glasgow-haskell-users
mailing list