Local definitions in the class instances

Max Bolingbroke batterseapower at hotmail.com
Wed Feb 2 12:36:16 CET 2011


On 2 February 2011 02:25, Sebastian Fischer <fischer at nii.ac.jp> wrote:
> It's a nice trick! Although it does look strange, it may be reasonable to
> allow pattern bindings in instance declarations regardless of the original
> proposal. Is it correct that, currently, pattern bindings are allowed
> everywhere but in instance declarations? If so, why not in instance
> declarations too?

Unfortunately, they are not allowed. I ran up against this limitation
even before this thread. Here is an example:

"""
{-# LANGUAGE NoMonoPatBinds #-}
data I a = I { unI :: a }

instance Monad I where
    (return, (>>=)) = (I, \mx f -> f (unI mx))

main = return ()
"""

And the error:

"""
/Users/mbolingbroke/Junk/InstancePattern.hs:5:5:
    Pattern bindings (except simple variables) not allowed in instance
declarations
      (return, >>=) = (I, \ mx f -> f (unI mx))
"""

This behaviour does seem to be as per the Haskell 98 spec, but I'm not
sure of the motivation behind it.

> I think the proposals to make pattern bindings monomorphic only concern
> pattern bindings without type annotations. Instance methods do have type
> annotations in the class declaration so even if pattern bindings without
> type signatures would be monomorphic, instance methods bound using pattern
> bindings need not be.

This was what I used to think too, but I recently found out (again,
unrelated to this thread) that they won't work even with explicit
signatures! See for example
http://hackage.haskell.org/trac/ghc/ticket/4940

I'm personally not in favour of MonoPatBinds anyway, but it is
*particularly* annoying that they don't work even with a signature.

Cheers,
Max



More information about the Haskell-prime mailing list