[Haskell-cafe] Re: Move MonadIO to base

Anders Kaseorg andersk at MIT.EDU
Mon Apr 19 02:15:06 EDT 2010


On Sun, 18 Apr 2010, wren ng thornton wrote:
>     lift ma = morph (\k -> join (fmap (k . return) ma))

Monad laws simplify that to
    lift ma = morph (\k -> ma >>= k . return)

> The type of morph requires us to Church-encode things needlessly; what 
> we mean to say is: morph (fmap return ma).

Hmm.  If I understand this (and your other emails) correctly, you’re 
saying my interface
    class Monad m => MonadMorphIO m where
        morphIO :: (forall b. (m a -> IO b) -> IO b) -> m a
should be equivalent to a simpler interface
    class Monad m => MonadJoinIO m where
        joinIO :: IO (m a) -> m a
via some isomorphism like
    morphIO f = joinIO (f return)
    joinIO m = morphIO (\w -> m >>= w)

I would be very happy to get the simpler interface to work, because it’s 
Haskell 98.  However, if I write
    joinIO m = morphIO (\w -> m >>= w)
    morphIO' f = joinIO (f return)
and define catch using morphIO' instead of morphIO:
    m `catch` h = morphIO $ \w -> w m `Control.Exception.catch` \e -> w (h e)
    m `catch'` h = morphIO' $ \w -> w m `Control.Exception.catch` \e -> w (h e)
then catch' fails to actually catch anything:

*Main> throwIO NonTermination `catch` \NonTermination -> return "moo"
"moo"
*Main> throwIO NonTermination `catch'` \NonTermination -> return "moo"
*** Exception: <<loop>>

Am I doing something wrong?

Anders


More information about the Haskell-Cafe mailing list