[Haskell-beginners] Inferred type is less polymorphic than e

Daniel Fischer daniel.is.fischer at web.de
Wed Apr 8 19:55:22 EDT 2009


Am Donnerstag 09 April 2009 00:29:24 schrieb Marco Túlio Gontijo e Silva:
> Hello,
>
> I'm getting this error message from GHC in the following code:
> > type M a = Monad m => m a
> >
> > class A a b where
> >   f :: Monad m => a -> m b
> >
> > instance A String Char where
> >   f string = return $ head string
> >
> > instance A Char Int where
> >   f int = return $ fromEnum int
>
> I thought at first to write h like this, but it gives me the error.  If
> I write it like the other h uncommented, there's no error.  I can't see
> why they aren't equivalent.
>
> h :: IO ()
> h = f "abc" >>= (f :: Char -> M Int) >>= print
>
> > h :: IO ()
> > h = (f "abc" :: M Char) >>= f >>= (print :: Int -> IO ())
>
> Can someone clarify this to me?
>
> Greetings.

The first error message when loading that code is

Inferred.hs:3:0:
    Illegal polymorphic or qualified type:
      forall (m :: * -> *). (Monad m) => m a
    Perhaps you intended to use -XRankNTypes or -XRank2Types
    In the type synonym declaration for `M'                 

That can be a hint. The type synonym M is probably not what you think.

This:
----------------------------------------------------------------
class B a b where
    foo :: a -> M b

instance B String Char where
    foo str = return $ head str

instance B Char Int where
    foo c = return $ fromEnum c

k :: IO ()
k = foo "abc" >>= (foo :: Char -> M Int) >>= print
----------------------------------------------------------------

works, as does

m = foo "abc" >>= (foo :: Char -> (forall x. Monad x => x Int)) >>= print

And that reveals what's going on, since m is in fact the same as k.
The type of f in class A says that given any specific monad m and a value of 
type a, f can produce a value of type m b.
But when you write
(f :: Char -> M Int)
, you say that given a Char, f produces a value which belongs to m Int *for 
every monad m*. Thus the type you state for f (the expected type) is more 
polymorphic than the actual type f has according to the class definition (which 
is the inferred type).



More information about the Beginners mailing list