ImplicitParams and MonoLocalBinds

Iavor Diatchki iavor.diatchki at gmail.com
Fri Mar 29 00:39:33 CET 2013


Hi,
This does not appear to be related to ImplicitParameters, rather
`MonoLocalBinds` is not working as expected.

Here is an example without implicit parameters that compiles just fine, but
would be rejected if `p` was monomorphic:

{-# LANGUAGE NoMonomorphismRestriction, MonoLocalBinds #-}

class C a where
  f :: a -> ()

instance C Bool where f = const ()
instance C Char where f = const ()

g = let p = f
    in (p 'a', p True)

-Iavor




On Fri, Mar 22, 2013 at 1:39 AM, Roman Cheplyaka <roma at ro-che.info> wrote:

> The value of the following expression
>
>   let ?y = 2  in
>   let  p = ?y in
>   let ?y = 1  in
>   p
>
> depends on whether the second binding is generalised.
>
> MonomorphismRestriction makes it not generalise, hence the value is 2.
>
> What surprises me is that MonoLocalBinds doesn't have this effect.
>
>   Prelude> :set -XImplicitParams -XNoMonomorphismRestriction
> -XMonoLocalBinds
>   Prelude> let ?y = 2 in let p = ?y in let ?y = 1 in p
>   1
>
> What's going on here?
>
> Roman
>
> _______________________________________________
> 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/20130328/356279cf/attachment.htm>


More information about the Glasgow-haskell-users mailing list