recursive group context bug?
Keean Schupke
k.schupke at imperial.ac.uk
Mon Jan 17 04:52:18 EST 2005
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?
>
>
>
More information about the Glasgow-haskell-users
mailing list