recursive group context bug?
Ashley Yakeley
ashley at semantic.org
Sun Jan 16 21:17:24 EST 2005
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
More information about the Glasgow-haskell-users
mailing list