Unexpected ambiguity in a seemingly valid Haskell 2010 program

Erik Hesselink hesselink at gmail.com
Sun Nov 11 19:33:30 CET 2012


That makes sense: MonomorphismRestriction makes bindings without parameters
monomorphic, and MonoLocalBinds makes local bindings monomorphic. So either
one will make this binding monomorphic. Only when both are off does it
become polymorphic and does the error occur.

Erik


On Sun, Nov 11, 2012 at 5:37 PM, Roman Cheplyaka <roma at ro-che.info> wrote:

> Right. What I meant is that with -XMonomorphismRestriction, it compiles
> with with both -XMonoLocalBinds and -XNoMonoLocalBinds.
>
> That means that MonoLocalBinds can not be solely responsible for this
> behaviour.
>
> Anyway, I just noticed that a very similar example (using Read) is
> described in the Haskell report's section on the monomorphism
> restriction.
>
> Roman
>
> * Erik Hesselink <hesselink at gmail.com> [2012-11-11 16:43:20+0100]
> > That's strange. Here, it only fails with both NoMonomorphismRestriction
> and
> > NoMonoLocalBinds (which makes sense). I've tested on 7.4.1 and 7.6.1.
> >
> > Erik
> >
> >
> > On Sun, Nov 11, 2012 at 3:54 PM, Roman Cheplyaka <roma at ro-che.info>
> wrote:
> >
> > > Apparently not — the code comilers with any of -XNoMonoLocalBinds and
> > > -XMonoLocalBinds, but not with -XNoMonomorphismRestriction.
> > >
> > > * wagnerdm at seas.upenn.edu <wagnerdm at seas.upenn.edu> [2012-11-09
> > > 14:07:59-0500]
> > > > 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
> > > > >
> > > > >
> > > >
> > > >
> > > > _______________________________________________
> > > > Glasgow-haskell-users mailing list
> > > > Glasgow-haskell-users at haskell.org
> > > > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> > >
> > > _______________________________________________
> > > Glasgow-haskell-users mailing list
> > > Glasgow-haskell-users at haskell.org
> > > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> > >
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20121111/0115bae0/attachment-0001.htm>


More information about the Glasgow-haskell-users mailing list