Re: [Haskell-cafe] Re: Move MonadIO to base

wren ng thornton wrote:
Anders Kaseorg wrote:
Yes; my question is more whether Wren has a more clever way to get an isomorphism (forall b. (m a -> IO b) -> IO b) <-> IO (m a) that would make the simpler interface work out. (Or maybe I misunderstood what he was getting at.)
Yeah no, that's what I was getting at. Since it doesn't quite work out, I should probably rethink my appeal to parametricity re Kleisli arrows.
No, my parametricity was correct, just the implementations were wrong: {-# LANGUAGE RankNTypes #-} module MorphIO where import Prelude hiding (catch) import Control.Monad import qualified Control.Exception as E import Control.Exception (NonTermination(..)) -- | The original class class Monad m => MonadMorphIO m where morphIO :: (forall b. (m a -> IO b) -> IO b) -> m a -- | The isomorphic Haskell98 version class Monad m => MonadJoinIO m where -- | Embed the IO into the monad m joinIO :: IO (m a) -> m a -- | Extract the IO computation to the top level, -- rendering the m pure from IO. partIO :: m a -> IO (m a) -- | The isomorphisms joinIO' m = morphIO (m >>=) morphIO' f = joinIO (f partIO) -- * Example instance MonadMorphIO IO where morphIO f = f id instance MonadJoinIO IO where joinIO = join partIO = fmap return -- N.B. fmap return /= return catch m h = morphIO $ \w -> w m `E.catch` \e -> w (h e) catch' m h = morphIO' $ \w -> w m `E.catch` \e -> w (h e) test = E.throwIO NonTermination `catch` \NonTermination -> return "moo" test' = E.throwIO NonTermination `catch'` \NonTermination -> return "moo" -- Live well, ~wren

On Tue, 20 Apr 2010, wren ng thornton wrote:
-- | The isomorphic Haskell98 version class Monad m => MonadJoinIO m where -- | Embed the IO into the monad m joinIO :: IO (m a) -> m a
-- | Extract the IO computation to the top level, -- rendering the m pure from IO. partIO :: m a -> IO (m a)
-- | The isomorphisms joinIO' m = morphIO (m >>=) morphIO' f = joinIO (f partIO)
To establish an isomorphism, you also need to define partIO from morphIO. For example, I don’t see how I could define partIO :: IO a -> IO (ReaderT r IO a) that extracts effects into the outer IO, because the effects depend on some unknown state of type r. By the way:
This bounced because I have different emails registered for cafe@ and libraries@, so forwarding it along to the cafe.
You can sign up both addresses for the list, then log in to the Mailman web interface ( http://www.haskell.org/mailman/listinfo/haskell-cafe → Unsubscribe or edit options) and disable mail delivery on one of them. Then you get one copy of each message but you can post from either address. Anders

Am 21.04.10 05:01, Anders Kaseorg wrote:
On Tue, 20 Apr 2010, wren ng thornton wrote:
-- | The isomorphic Haskell98 version class Monad m => MonadJoinIO m where -- | Embed the IO into the monad m joinIO :: IO (m a) -> m a
-- | Extract the IO computation to the top level, -- rendering the m pure from IO. partIO :: m a -> IO (m a)
-- | The isomorphisms joinIO' m = morphIO (m >>=) morphIO' f = joinIO (f partIO)
To establish an isomorphism, you also need to define partIO from morphIO. For example, I don’t see how I could define partIO :: IO a -> IO (ReaderT r IO a) that extracts effects into the outer IO, because the effects depend on some unknown state of type r.
I think you mean partIO :: ReaderT r IO a -> IO (ReaderT r IO a) This does not affect the impossibility of pushing the effect to the outer IO. On a side note, joinIO = join . liftIO Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com
participants (3)
-
Anders Kaseorg
-
Heinrich Apfelmus
-
wren ng thornton