recursive group context bug?

Keean Schupke k.schupke at imperial.ac.uk
Mon Jan 17 07:48:47 EST 2005


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
>  
>



More information about the Glasgow-haskell-users mailing list