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

Marco Túlio Gontijo e Silva marcot at holoscopio.com
Thu Apr 9 07:16:01 EDT 2009


Em Qui, 2009-04-09 às 01:55 +0200, Daniel Fischer escreveu:
> 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 ())
> >
> ----------------------------------------------------------------
> 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).

Ok, I got it, so I tried changing class A in my example to:

> class A a b where
>   f :: forall m . Monad m => a -> m b

so that the type of f would be as polymorphic as the type a -> M b.  But
I got the same problem.

Your solution is good, but I can't do it in my real application where I
find out this problem, because the type synonym M is defined after the
class A, and it contains more than on type constraint:

> type Interpret value
>   = ( MonadReader Input monad
>     , MonadState Machine monad
>     , MonadWriter Stream monad)
>   => monad value

My use is that I have some classes defined in modules included by the
one that defines type Interpret, like this:

> class Value pointer value where
>   getValue
>     :: (MonadReader Program monad, MonadState Machine monad)
>     => pointer -> monad value

And even if they were defined in the same file, it would not be good to
define them as Interpret, because it would restrict its type.

Another thing:  I understand your explanation, but I don't get why this
makes the other h definition valid.  Could you clarify me on that?

Thanks.

-- 
marcot
http://marcot.iaaeee.org/




More information about the Beginners mailing list