
I suspect someone's come across this before, so maybe there's an explanation for it. This does not compile: module Bug where { p :: IO (); p = q >>= id; q :: (Monad m) => m (IO ()); q = return p; } Bug.hs:3: Mismatched contexts When matching the contexts of the signatures for p :: IO () q :: forall m. (Monad m) => m (IO ()) The signature contexts in a mutually recursive group should all be identical When generalising the type(s) for p, q The code looks correct to me. Why must the signature contexts be identical in this case? -- Ashley Yakeley, Seattle WA

You cannot sequence two operations from different monads... p has type: m (IO ()) id has type, IO () (in this case because this is what p returns)... You can do: p :: (Monad m) => m (IO ()) p = q >>= (\a -> return a) Or p :: (Monad m) => m (IO ()) p = run q >>= id -- provided an overloaded definition of run is provided for 'm' Keean. Ashley Yakeley wrote:
I suspect someone's come across this before, so maybe there's an explanation for it.
This does not compile:
module Bug where { p :: IO (); p = q >>= id;
q :: (Monad m) => m (IO ()); q = return p; }
Bug.hs:3: Mismatched contexts When matching the contexts of the signatures for p :: IO () q :: forall m. (Monad m) => m (IO ()) The signature contexts in a mutually recursive group should all be identical When generalising the type(s) for p, q
The code looks correct to me. Why must the signature contexts be identical in this case?

On Mon, Jan 17, 2005 at 09:52:18AM +0000, Keean Schupke wrote:
You cannot sequence two operations from different monads...
Note that this compiles: module Bug where { p :: IO (); p = q >>= id; q :: (Monad m) => m (IO ()); q = return (return ()); -- the only change is in this line } Best regards, Tomasz

I suspect its becuse q needs to get the dictionary for 'm' from somewhere... as it is recursive, p calls q calls p, so p must have the dictionary for 'm' in its context... So this works: module Main where p :: Monad m => m () p = q >>= id q :: Monad m => m (m ()) q = return p Keean. Tomasz Zielonka wrote:
On Mon, Jan 17, 2005 at 09:52:18AM +0000, Keean Schupke wrote:
You cannot sequence two operations from different monads...
Note that this compiles:
module Bug where
p :: IO (); p = q >>= id;
q :: (Monad m) => m (IO ()); q = return (return ()); -- the only change is in this line }
Best regards, Tomasz

Oops, I initially hit r instead of L... -- Carsten Schultz (2:38, 33:47), FB Mathematik, FU Berlin http://carsten.codimi.de/ PGP/GPG key on the pgp.net key servers, fingerprint on my home page.
participants (4)
-
Ashley Yakeley
-
Carsten Schultz
-
Keean Schupke
-
Tomasz Zielonka