Move MonadIO to base

Hello, Some people have remarked that the MonadIO class would be better of in the base package instead of mtl/transformers. It can be used largely independently from the monad transformers, and it is useful without them. This has been previously discussed [1,2], but as far as I know nothing ever came of it. If MonadIO were in base, then the base library itself could also use it. For example the functions in System.IO could be lifted to work on any MonadIO monad. Whether that is a good idea is completely orthogonal to this discussion, however. How hard would it be to make this change? For backwards compatibility mtl and transformers would need a check to see which version of base is used, or new versions of mtl/transformers should just not include MonadIO. Twan [1] http://www.haskell.org/pipermail/libraries/2009-December/012914.html [2] http://hackage.haskell.org/trac/ghc/ticket/3777

On Sat, Apr 10, 2010 at 10:35 AM, Twan van Laarhoven
Hello,
Some people have remarked that the MonadIO class would be better of in the base package instead of mtl/transformers. It can be used largely independently from the monad transformers, and it is useful without them.
This has been previously discussed [1,2], but as far as I know nothing ever came of it.
If MonadIO were in base, then the base library itself could also use it. For example the functions in System.IO could be lifted to work on any MonadIO monad. Whether that is a good idea is completely orthogonal to this discussion, however.
How hard would it be to make this change? For backwards compatibility mtl and transformers would need a check to see which version of base is used, or new versions of mtl/transformers should just not include MonadIO.
+1 from me. Sorry for dropping the last thread, but that was the conclusion it seemed to come to. I'm not as sure about moving MonadTrans to Base, but that's because I never use it. Antoine

+1 from me.
Also, there is some (very recent) work in transformers for splitting apart
Control.Monad.Trans into a module for IO and one for MonadTrans, so the
scaffolding to support this is already in place.
http://osdir.com/ml/libraries@haskell.org/2010-03/msg00233.html
-Edward Kmett
On Sat, Apr 10, 2010 at 1:35 PM, Antoine Latter
Hello,
Some people have remarked that the MonadIO class would be better of in
On Sat, Apr 10, 2010 at 10:35 AM, Twan van Laarhoven
wrote: the base package instead of mtl/transformers. It can be used largely independently from the monad transformers, and it is useful without them.
This has been previously discussed [1,2], but as far as I know nothing ever came of it.
If MonadIO were in base, then the base library itself could also use it. For example the functions in System.IO could be lifted to work on any MonadIO monad. Whether that is a good idea is completely orthogonal to this discussion, however.
How hard would it be to make this change? For backwards compatibility mtl and transformers would need a check to see which version of base is used, or new versions of mtl/transformers should just not include MonadIO.
+1 from me.
Sorry for dropping the last thread, but that was the conclusion it seemed to come to. I'm not as sure about moving MonadTrans to Base, but that's because I never use it.
Antoine _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Sat, Apr 10, 2010 at 8:35 AM, Twan van Laarhoven
Hello,
Some people have remarked that the MonadIO class would be better of in the base package instead of mtl/transformers. It can be used largely independently from the monad transformers, and it is useful without them.
This has been previously discussed [1,2], but as far as I know nothing ever came of it.
If MonadIO were in base, then the base library itself could also use it. For example the functions in System.IO could be lifted to work on any MonadIO monad. Whether that is a good idea is completely orthogonal to this discussion, however.
How hard would it be to make this change? For backwards compatibility mtl and transformers would need a check to see which version of base is used, or new versions of mtl/transformers should just not include MonadIO.
Twan
[1] http://www.haskell.org/pipermail/libraries/2009-December/012914.html [2] http://hackage.haskell.org/trac/ghc/ticket/3777
+1 from me as well, I just wrote some code that would *love* to have MonadIO available but I couldn't tie down to mtl or transformers.
Michael

On Sat, Apr 10, 2010 at 05:35:53PM +0200, Twan van Laarhoven wrote:
Some people have remarked that the MonadIO class would be better of in the base package instead of mtl/transformers.
+1.
If MonadIO were in base, then the base library itself could also use it. For example the functions in System.IO could be lifted to work on any MonadIO monad. Whether that is a good idea is completely orthogonal to this discussion, however.
+1 as well. Thanks, -- Felipe.

Twan van Laarhoven wrote:
If MonadIO were in base, then the base library itself could also use it. For example the functions in System.IO could be lifted to work on any MonadIO monad. Whether that is a good idea is completely orthogonal to this discussion, however.
The main problem is that exceptions don't work well with MonadIO in GHC. So really MonadIO is currently only a toy and cannot be used in production code. The reason for this is that just about any operation involving exceptions ultimately depends (via the source code of base library functions) on the function block :: IO a -> IO a and that type is hard-wired in a GHC primitive. Additional primitives to support things like startBlocking :: IO () stopBlocking :: IO () which would play well with MonadIO, could be added to GHC, but they would lose important optimizations. I'm not sure about the order of magnitude of the cost - whether it would just make things run more slowly, or render them completely unusable. If the former, I am in favor of this proposal, but only combined with the addition of GHC support for startBlocking and stopBlocking. If the latter, then there is no point to this proposal. Regards, Yitz

On Sun, Apr 11, 2010 at 5:35 PM, Yitzchak Gale
Twan van Laarhoven wrote:
If MonadIO were in base, then the base library itself could also use it. For example the functions in System.IO could be lifted to work on any MonadIO monad. Whether that is a good idea is completely orthogonal to this discussion, however.
The main problem is that exceptions don't work well with MonadIO in GHC. So really MonadIO is currently only a toy and cannot be used in production code.
The reason for this is that just about any operation involving exceptions ultimately depends (via the source code of base library functions) on the function
block :: IO a -> IO a
and that type is hard-wired in a GHC primitive.
Can you explain why this is a problem? Do note we have the packages MonadCatchIO-transformers[1] and MonadCatchIO-mtl[2] that both provide: class MonadIO m => MonadCatchIO m where catch :: Exception e => m a -> (e -> m a) -> m a block :: m a -> m a unblock :: m a -> m a
Additional primitives to support things like
startBlocking :: IO () stopBlocking :: IO ()
which would play well with MonadIO, could be added to GHC, but they would lose important optimizations. I'm not sure about the order of magnitude of the cost - whether it would just make things run more slowly, or render them completely unusable. If the former, I am in favor of this proposal, but only combined with the addition of GHC support for startBlocking and stopBlocking. If the latter, then there is no point to this proposal.
Note that currently a discussion[3] is going on about hiding 'block' and 'unblock' and replacing them with: mask :: ((IO a -> IO a) -> IO b) -> IO b mask io = do b <- blocked if b then io id else block $ io unblock to be used like this: a `finally` b = mask $ \restore -> do r <- restore a `onException` b b return r Of course when this change is made the MonadCatchIO class has to be adapted to something like: class MonadIO m => MonadCatchIO m where catch :: Exception e => m a -> (e -> m a) -> m a mask :: ((m b -> m b) -> m a) -> m a instance MonadCatchIO IO where catch = Control.Exception.catch mask io = do b <- blocked if b then io id else block $ io unblock instance MonadCatchIO m => MonadCatchIO (ReaderT r m) where m `catch` f = ReaderT $ \r -> runReaderT m r `catch` \e -> runReaderT (f e) r mask io = ReaderT inner where inner r = mask innerIO where innerIO innerRestore = runReaderT (io restore) r where restore reader = ReaderT $ innerRestore . runReaderT reader Note I'm +1 for separating MonadIO from transformers and mtl. I'm not sure yet about putting it in base. regards, Bas [1] http://hackage.haskell.org/package/MonadCatchIO-transformers [2] http://hackage.haskell.org/package/MonadCatchIO-mtl [3] http://thread.gmane.org/gmane.comp.lang.haskell.cafe/72145/focus=72182

On Sun, Apr 11, 2010 at 8:48 PM, Bas van Dijk
[3] http://thread.gmane.org/gmane.comp.lang.haskell.cafe/72145/focus=72182
Sorry this is the correct link to Simon Marlow's new proposal: http://thread.gmane.org/gmane.comp.lang.haskell.cafe/72145/focus=72972 Bas

On Sun, 11 Apr 2010, Bas van Dijk wrote:
Of course when this change is made the MonadCatchIO class has to be adapted to something like:
class MonadIO m => MonadCatchIO m where catch :: Exception e => m a -> (e -> m a) -> m a mask :: ((m b -> m b) -> m a) -> m a
The striking similarity between instances of MonadCatchIO suggests to me that something deeper is going on. Is there a cleaner abstraction that captures this idea? instance ( MonadCatchIO m) => MonadCatchIO (ReaderT r m) where m `catch` f = ReaderT $ \r -> runReaderT m r `catch` \e -> runReaderT (f e) r mask io = ReaderT $ \r -> mask $ \restore -> runReaderT (io $ mapReaderT restore) r instance ( MonadCatchIO m) => MonadCatchIO (StateT s m) where m `catch` f = StateT $ \s -> runStateT m s `catch` \e -> runStateT (f e) s mask io = StateT $ \s -> mask $ \restore -> runStateT (io $ mapStateT restore) s instance (Error e, MonadCatchIO m) => MonadCatchIO (ErrorT e m) where m `catch` f = ErrorT $ runErrorT m `catch` \e -> runErrorT (f e) mask io = ErrorT $ mask $ \restore -> runErrorT (io $ mapErrorT restore) instance (Monoid r, MonadCatchIO m) => MonadCatchIO (WriterT r m) where m `catch` f = WriterT $ runWriterT m `catch` \e -> runWriterT (f e) mask io = WriterT $ mask $ \restore -> runWriterT (io $ mapWriterT restore) instance (Monoid w, MonadCatchIO m) => MonadCatchIO (RWST r w s m) where m `catch` f = RWST $ \r s -> runRWST m r s `catch` \e -> runRWST (f e) r s mask io = RWST $ \r s -> mask $ \restore -> runRWST (io $ mapRWST restore) r s instance ( MonadCatchIO m) => MonadCatchIO (ListT m) where m `catch` f = ListT $ runListT m `catch` \e -> runListT (f e) mask io = ListT $ mask $ \restore -> runListT (io $ mapListT restore) instance ( MonadCatchIO m) => MonadCatchIO (ContT r m) where m `catch` f = ContT $ \c -> runContT m c `catch` \e -> runContT (f e) c mask io = ContT $ \c -> mask $ \restore -> runContT (io $ mapContT restore) c (By the way, these last two don’t seem to be in the current MonadCatchIO packages. Any reason why not?) Anders

On Tue, 13 Apr 2010, Anders Kaseorg wrote:
The striking similarity between instances of MonadCatchIO suggests to me that something deeper is going on. Is there a cleaner abstraction that captures this idea?
Here a possible answer. I haven’t entirely figured out what it “means” yet, but maybe someone who knows more category theory will be able to figure that out. :-) class Monad m => MonadMorphIO m where morphIO :: (forall b. (m a -> IO b) -> IO b) -> m a instance MonadMorphIO IO where morphIO f = f id instance MonadMorphIO m => MonadMorphIO (ReaderT r m) where morphIO f = ReaderT $ \r -> morphIO $ \w -> f $ \m -> w $ runReaderT m r instance MonadMorphIO m => MonadMorphIO (StateT s m) where morphIO f = StateT $ \s -> morphIO $ \w -> f $ \m -> w $ runStateT m s instance (Error e, MonadMorphIO m) => MonadMorphIO (ErrorT e m) where morphIO f = ErrorT $ morphIO $ \w -> f $ \m -> w $ runErrorT m instance (Monoid w, MonadMorphIO m) => MonadMorphIO (WriterT w m) where morphIO f = WriterT $ morphIO $ \w -> f $ \m -> w $ runWriterT m instance (Monoid w, MonadMorphIO m) => MonadMorphIO (RWST r w s m) where morphIO f = RWST $ \r s -> morphIO $ \w -> f $ \m -> w $ runRWST m r s instance MonadMorphIO m => MonadMorphIO (ListT m) where morphIO f = ListT $ morphIO $ \w -> f $ \m -> w $ runListT m instance MonadMorphIO m => MonadMorphIO (ContT r m) where morphIO f = ContT $ \c -> morphIO $ \w -> f $ \m -> w $ runContT m c catch :: MonadMorphIO m => Exception e => m a -> (e -> m a) -> m a m `catch` h = morphIO $ \w -> w m `Control.Exception.catch` \e -> w (h e) mask :: MonadMorphIO m => ((forall b. m b -> m b) -> m a) -> m a mask io = morphIO $ \w -> mask_IO $ \restore -> w $ io $ \m -> morphIO $ \w' -> restore (w' m) where mask_IO :: ((forall b. IO b -> IO b) -> IO a) -> IO a mask_IO io = do b <- blocked if b then io id else block $ io unblock You can avoid all the RankNTypes if you use TypeFamilies (or MultiParamTypeClasses+FunctionalDependencies, if you want) to be more specific about which type b is: class Monad m => MonadMorphIO m where data Result m :: * -> * morphIO :: ((m a -> IO (Result m a)) -> IO (Result m a)) -> m a instance MonadMorphIO m => MonadMorphIO (StateT s m) where newtype Result (StateT s m) a = StateTResult { runStateTResult :: Result m (a, s) } morphIO f = morphStateT $ \w -> morphIO $ \w' -> liftM runStateTResult $ f $ liftM StateTResult . w' . w This concept can also be generalized to monad transformers: class MonadTrans t => MonadTransMorph t where morph :: Monad m => (forall b. (t m a -> m b) -> m b) -> t m a instance MonadTransMorph (StateT s) where morph f = StateT $ \s -> f $ \m -> runStateT m s Anders

Anders Kaseorg wrote:
On Tue, 13 Apr 2010, Anders Kaseorg wrote:
The striking similarity between instances of MonadCatchIO suggests to me that something deeper is going on. Is there a cleaner abstraction that captures this idea?
Here a possible answer. I haven’t entirely figured out what it “means” yet, but maybe someone who knows more category theory will be able to figure that out. :-)
class Monad m => MonadMorphIO m where morphIO :: (forall b. (m a -> IO b) -> IO b) -> m a
This is broadly related to Church encoding and CPS conversion. For example sums, products, and recursion can be encoded via: (forall r. (X->r) -> (Y->r) -> r) ~= X+Y == Either X Y (forall r. (X->Y->r) -> r) ~= X*Y == (X,Y) (forall r. (X->r->r) -> r -> r) == (forall r. (X->r->r) -> (()->r) -> r) ~= fix r. X*r + 1 == [X] So if we ignore the IO parts, then your class is isomorphic to newtype F m a = MkF (m a) class Monad m => MonadMorphIO where morphIO :: F m a -> m a But that's ignoring the IO. So what is this class saying, with the IO? Well, what does (m a -> IO b) mean? One view treats IO as merely a type constructor, in which case it means ((_->_) (m a) (IO b)), i.e. a morphism in Hask from (m a) to (IO b). But since IO is a monad we could also think of the Kleisli category generated by IO, in which case it means ((_ -> IO _) (m a) b), i.e. a morphism in the IO category from (m a) to b. Putting these together, your class means: if you can construct/eliminate an (F m a) in the IO category, then you can construct an (m a) in the Hask category. I.e., IO(m a) is a subset of (m a). -- Live well, ~wren

wren ng thornton wrote:
Anders Kaseorg wrote:
On Tue, 13 Apr 2010, Anders Kaseorg wrote:
The striking similarity between instances of MonadCatchIO suggests to me that something deeper is going on. Is there a cleaner abstraction that captures this idea?
Here a possible answer. I haven’t entirely figured out what it “means” yet, but maybe someone who knows more category theory will be able to figure that out. :-)
class Monad m => MonadMorphIO m where morphIO :: (forall b. (m a -> IO b) -> IO b) -> m a
[...] Putting these together, your class means: if you can construct/eliminate an (F m a) in the IO category, then you can construct an (m a) in the Hask category. I.e., IO(m a) is a subset of (m a).
Which is more general than liftIO which only says (IO a) is a subset of (m a). That is, liftIO requires that the non-IO layers of m are constructed via `return`, whereas morphIO permits non-pointed use of IO. In other words, liftIO only allows lifting "effectful" values, whereas morphIO also allows lifting "structural" values. -- Live well, ~wren

On April 16, 2010 01:46:43 wren ng thornton wrote:
wren ng thornton wrote:
Anders Kaseorg wrote:
class Monad m => MonadMorphIO m where morphIO :: (forall b. (m a -> IO b) -> IO b) -> m a
[...] Putting these together, your class means: if you can construct/eliminate an (F m a) in the IO category, then you can construct an (m a) in the Hask category. I.e., IO(m a) is a subset of (m a).
Which is more general than liftIO which only says (IO a) is a subset of (m a). That is, liftIO requires that the non-IO layers of m are constructed via `return`, whereas morphIO permits non-pointed use of IO. In other words, liftIO only allows lifting "effectful" values, whereas morphIO also allows lifting "structural" values.
Are you then saying that liftIO should be able to be defined via morphIO? I would be curious to see that as, after a bit of trying, I still can't see how to. Specifically, I can't capture the results of the desired IO operation. If it is complementary to liftIO, and not strictly more powerful, maybe it should be named lowerIO because it's function seems to be that it gives the ability to lower (or push) a computation down onto the IO layer. Cheers! -Tyson

On Fri, 23 Apr 2010, Tyson Whitehead wrote:
Are you then saying that liftIO should be able to be defined via morphIO? I would be curious to see that as, after a bit of trying, I still can't see how to. Specifically, I can't capture the results of the desired IO operation.
Yes, just like lift is defined via morph: liftIO' :: (MonadMorphIO m) => IO a -> m a liftIO' m = morphIO $ \down -> m >>= down . return main = runContT (runReaderT main' ()) return main' = do liftIO' $ putStrLn "What is your name?" name <- liftIO' $ getLine liftIO' $ putStrLn $ "Hello " ++ name Anders

On April 23, 2010 13:39:36 Anders Kaseorg wrote:
Yes, just like lift is defined via morph:
liftIO' :: (MonadMorphIO m) => IO a -> m a liftIO' m = morphIO $ \down -> m >>= down . return
Thanks. That make sense. How about "exposeIO" for a name then? It references the fact that it exposes the underlying IO monad. Or even "peakIO", "glimpseIO", "teaseIO", or so on, as it is not a full exposure, but just enough to apply combinators. Really though, as you (or someone else) said, it would seem to be a pretty basic as useful functionality that any of the monad transfers should expose (in this universally quantified way) the monad they are built upon. Cheers! -Tyson

On Friday 23 April 2010 1:39:36 pm Anders Kaseorg wrote:
On Fri, 23 Apr 2010, Tyson Whitehead wrote:
Are you then saying that liftIO should be able to be defined via morphIO? I would be curious to see that as, after a bit of trying, I still can't see how to. Specifically, I can't capture the results of the desired IO operation.
Yes, just like lift is defined via morph:
liftIO' :: (MonadMorphIO m) => IO a -> m a liftIO' m = morphIO $ \down -> m >>= down . return
main = runContT (runReaderT main' ()) return main' = do liftIO' $ putStrLn "What is your name?" name <- liftIO' $ getLine liftIO' $ putStrLn $ "Hello " ++ name
Can lift really be defined from morph, though? Given just: class MonadTrans t where morph :: Monad m => (forall b. (t m a -> m b) -> m b) -> t m a trying to define: lift :: (Monad m, MonadTrans t) => m a -> t m a lift m = morph (\k -> m >>= k . return) yields an error. Monad m and MonadTrans t do not imply Monad (t m), which is what that definition requires. Now, it's not possible to define a Monad (t m) instance using the traditional class, because there's no way to define (>>=). So, despite the fact that t m should always be a monad, that isn't something we're allowed to assume for a general case (since, indeed, the instance may not be declared). The one thing we can define with lift is return, as: return x = lift (return x) however, this is no help, because we're using return to try and define lift via morph. And it doesn't look to me that there's a better way to define return via morph: * We're given an x : a and f : (forall b. (t m a -> m b) -> m b) -> t m a * We need to produce a (t m a); the only way to do this is to call f * f (\k -> ...) - Now we have k : t m a -> m b, and need to produce an (m b) - But producing a (t m a) from an a is what we're trying to do in the first place. We can't recurse, though, as that'd just be infinite recursion (to compute return' f x, compute return' f x). So I don't think there's anything to be done. lift cannot be defined from morph unless you make assumptions that are not permissible (unless I've missed something). liftIO from morphIO is different, because the precondition on MonadMorphIO has ensured that the analogue of (t m) is actually a monad, with a non-circular definition of return. -- Dan

On Fri, Apr 23, 2010 at 3:46 PM, Dan Doel
On Friday 23 April 2010 1:39:36 pm Anders Kaseorg wrote:
On Fri, 23 Apr 2010, Tyson Whitehead wrote:
Are you then saying that liftIO should be able to be defined via morphIO? I would be curious to see that as, after a bit of trying, I still can't see how to. Specifically, I can't capture the results of the desired IO operation.
Yes, just like lift is defined via morph:
liftIO' :: (MonadMorphIO m) => IO a -> m a liftIO' m = morphIO $ \down -> m >>= down . return
main = runContT (runReaderT main' ()) return main' = do liftIO' $ putStrLn "What is your name?" name <- liftIO' $ getLine liftIO' $ putStrLn $ "Hello " ++ name
Can lift really be defined from morph, though? Given just:
class MonadTrans t where morph :: Monad m => (forall b. (t m a -> m b) -> m b) -> t m a
trying to define:
lift :: (Monad m, MonadTrans t) => m a -> t m a lift m = morph (\k -> m >>= k . return)
yields an error. Monad m and MonadTrans t do not imply Monad (t m), which is what that definition requires.
This works for me:
lift :: (MonadTrans t, Monad m, Monad (t m)) => m a -> t m a
lift m = morph (\d -> m >>= d . return)
Ideally, we'd be able to give (forall m. Monad m => Monad (t m)) as a
requirement of MonadTrans. As it happens, my own monad library
simulates that with an extra class.
class MonadTrans t where
return1 :: Monad m => a -> t m a
bind1 :: Monad m => t m a -> (a -> t m b) -> t m b
class MonadTrans t => MonadLift t where
lift :: Monad m => m a -> t m a
This is pretty straightforward to extend:
class MonadLift t => MonadMorph t where
morph :: Monad m => (forall b. (t m a -> m b) -> m b) -> t m a
lift_ :: (MonadMorph t, Monad m) => m a -> t m a
lift_ m = morph (\d -> m >>= d . return1)
The question I would ask is whether morph can be sensibly defined for
the backtracking monad. It's a good example of a class of monads which
are more complicated than the usual state and exceptions stuff, but
not as powerful or complex as ContT.
--
Dave Menendez

David Menendez wrote:
On Fri, Apr 23, 2010 at 3:46 PM, Dan Doel
wrote: Monad m and MonadTrans t do not imply Monad (t m), which is what that definition requires.
This works for me:
lift :: (MonadTrans t, Monad m, Monad (t m)) => m a -> t m a lift m = morph (\d -> m >>= d . return)
I think the point was that the current definition of lift does not have a Monad(t m) constraint and therefore the above definition doesn't suffice because it imposes additional requirements. (Granted they're desirable requirements, but all the same.) We don't actually need all of Monad(t m). The only thing we need is some general function: returnT :: (MonadTrans t, Monad m) => a -> t m a Though that's not possible, since t is held abstract and MonadTrans only offers to construct one if you can provide a function to destruct them. So alternatively, we could use morph to construct returnT if only we had the general function: -- where B is some type associated with the t. foo :: (MonadTrans t, Monad m) => t m a -> m B Which, of course, we can't do either since we don't even know which type B is (when t is held abstract). Thus, the only ways to define lift using morph are: (1) add a (Monad (t m)) constraint to morph (1') add an (Applicative (t m)) constraint to morph (1'') define a class for pointed functors and add (Pointed(t m)) (2) add the returnT function to the MonadTrans class (3) add an MPTC/associated type B and the function foo to the MonadTrans class (4) some similar hackery I've overlooked. -- Live well, ~wren

On Fri, Apr 23, 2010 at 9:09 PM, wren ng thornton
David Menendez wrote:
On Fri, Apr 23, 2010 at 3:46 PM, Dan Doel
wrote: Monad m and MonadTrans t do not imply Monad (t m), which is what that definition requires.
This works for me:
lift :: (MonadTrans t, Monad m, Monad (t m)) => m a -> t m a lift m = morph (\d -> m >>= d . return)
I think the point was that the current definition of lift does not have a Monad(t m) constraint and therefore the above definition doesn't suffice because it imposes additional requirements. (Granted they're desirable requirements, but all the same.)
It makes explicit certain implicit requirements. Instances of
MonadTrans are intended to map monads to monads (forall m. Monad m =>
Monad (t m)).
Admittedly, the MTL is woefully under-specified, but you would expect
lift to satisfy these properties:
lift (return x) = return x
lift (e >>= f) = lift e >>= lift . f
which are only meaningful if there's an implicit Monad (t m) constraint on lift.
In any case, I don't think anyone is talking about adding morph to the
standard monad libraries yet. It's only general enough to promote a
subset of monad operations (mplus and catch), and it only applies to a
subset of monad transformers (state reader/writer/transformer and
exceptions).
N.B. The instance given for ContT does not do what you want. Here's
the definition again:
morphIO f = ContT $ \k -> morphIO (\d -> f (\m -> d (runContT m k)))
Note that the entire continuation is passed to d. If you are defining,
say, block in terms of morphIO
gblock m = morphIO (\d -> block (d m))
Then m and its continuation get masked, not just m. Similar problems
occur for backtracking monads and iteratees.
--
Dave Menendez

On April 23, 2010 21:55:52 David Menendez wrote:
N.B. The instance given for ContT does not do what you want. Here's the definition again:
morphIO f = ContT $ \k -> morphIO (\d -> f (\m -> d (runContT m k)))
Note that the entire continuation is passed to d. If you are defining, say, block in terms of morphIO
gblock m = morphIO (\d -> block (d m))
Then m and its continuation get masked, not just m. Similar problems occur for backtracking monads and iteratees.
I think you have to redo ContT so the underlying monad is exposed to the continuation instead of being permanently trapped inside a closure. newtype ContT m a = ContT { runContT :: forall r. (m a -> m r) -> m r } class MorphIO m where morphIO :: (forall b. (m a -> IO b) -> IO b) -> m a instance Monad m => Monad (ContT m) where return x = ContT $ \k -> k $ return x m >>= f = ContT $ \k -> runContT m (>>= \x -> runContT (f x) k) instance MorphIO m => MorphIO (ContT m) where morphIO f = ContT $ \k -> k $ morphIO $ \d -> f $ \m -> d $ runContT m id Now just the single desired computation is being passed to d, which is then re-wrapped and passed onto the continuation. Cheers! -Tyson

Anders Kaseorg wrote:
The striking similarity between instances of MonadCatchIO suggests to me that something deeper is going on. Is there a cleaner abstraction that captures this idea?
Here a possible answer. I haven’t entirely figured out what it “means” yet, but maybe someone who knows more category theory will be able to figure that out. :-)
class Monad m => MonadMorphIO m where morphIO :: (forall b. (m a -> IO b) -> IO b) -> m a
instance MonadMorphIO IO where morphIO f = f id instance MonadMorphIO m => MonadMorphIO (ReaderT r m) where morphIO f = ReaderT $ \r -> morphIO $ \w -> f $ \m -> w $ runReaderT m r
[...]
This concept can also be generalized to monad transformers:
class MonadTrans t => MonadTransMorph t where morph :: Monad m => (forall b. (t m a -> m b) -> m b) -> t m a
instance MonadTransMorph (StateT s) where morph f = StateT $ \s -> f $ \m -> runStateT m s
Interesting! (Cross posting this to cafe) In the light of Conor's remark on the distinction between "operations" and "control operators" http://www.haskell.org/pipermail/haskell-cafe/2010-April/076185.html , it appears that the essence of MonadTransIO is the ability to lift control operators, whereas MonadTrans can only lift operations. For instance, here is a lifting of mplus : mplus' :: MonadPlus m => StateT s m a -> StateT s m a -> StateT s m a mplus' x y = morph $ \down -> down x `mplus` down y I believe this corresponds to a "commuting product" of State with the monad m in Gordon Plotkins language?
You can avoid all the RankNTypes if you use TypeFamilies (or MultiParamTypeClasses+FunctionalDependencies, if you want) to be more specific about which type b is:
class Monad m => MonadMorphIO m where data Result m :: * -> * morphIO :: ((m a -> IO (Result m a)) -> IO (Result m a)) -> m a
instance MonadMorphIO m => MonadMorphIO (StateT s m) where newtype Result (StateT s m) a = StateTResult { runStateTResult :: Result m (a, s) } morphIO f = morphStateT $ \w -> morphIO $ \w' -> liftM runStateTResult $ f $ liftM StateTResult . w' . w
This would make it possible to lift control operators with more restricted return types. Not that I know any useful examples. However, not all control operators can be lifted this way. Essentially, while you may "downgrade" an arbitrary selection of t m a values you may only promote one m a in return and all have to share the same return type a . In particular, it's not possible to implement lift :: (Monad m, MonadTrans t) => m a -> t m a in terms of morph. Is there a way to lift really *any* control operator, or at least a good overview of those that can be lifted? There's also the question of how to characterize morph in terms of equations. The following is immediate morph ($ m) = m but relating morph with >>= seems to be tricker because of the opaque return type b . Maybe this: morph ((m >>=) . h) = lift m >>= morph . flip h I haven't found an equation for return . Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Heinrich Apfelmus wrote:
Anders Kaseorg wrote:
This concept can also be generalized to monad transformers:
class MonadTrans t => MonadTransMorph t where morph :: Monad m => (forall b. (t m a -> m b) -> m b) -> t m a
[...] However, not all control operators can be lifted this way. Essentially, while you may "downgrade" an arbitrary selection of t m a values you may only promote one m a in return and all have to share the same return type a . In particular, it's not possible to implement
lift :: (Monad m, MonadTrans t) => m a -> t m a
Why not? * morph says m(t m a) is a subset of (t m a) * Monad m says we can fmap :: (a->b) -> (m a->m b) * Monad (t m) says we can return :: a -> t m a lift ma = morph (\k -> k (fmap return ma)) Again, having m(t m a)->(t m a) is strictly more expressive than only having (m a)->(t m a) because the former may avail itself of operations/operators of t. -- Live well, ~wren

wren ng thornton wrote:
Heinrich Apfelmus wrote:
Anders Kaseorg wrote:
This concept can also be generalized to monad transformers:
class MonadTrans t => MonadTransMorph t where morph :: Monad m => (forall b. (t m a -> m b) -> m b) -> t m a
[...] However, not all control operators can be lifted this way. Essentially, while you may "downgrade" an arbitrary selection of t m a values you may only promote one m a in return and all have to share the same return type a . In particular, it's not possible to implement
lift :: (Monad m, MonadTrans t) => m a -> t m a
Why not? * morph says m(t m a) is a subset of (t m a) * Monad m says we can fmap :: (a->b) -> (m a->m b) * Monad (t m) says we can return :: a -> t m a
lift ma = morph (\k -> k (fmap return ma))
Or rather, lift ma = morph (\k -> join (fmap (k . return) ma)) That's what I get for typing without checking. The type of morph requires us to Church-encode things needlessly; what we mean to say is: morph (fmap return ma). -- Live well, ~wren

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

On 04/19/10 02:15, Anders Kaseorg wrote:
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?
Well, let's see what happens if we apply it to the fairly easy
instance MonadMorphIO IO where morphIO f = f id
then joinIO m = morphIO (\w -> m >>= w) = (\w -> m >>= w) (id) = m >>= id = join m morphIO' f = joinIO (f return) = join (f return) morphIO = f id m `catch` h = morphIO $ \w -> w m `Control.Exception.catch` \e -> w (h e) [w = id] = id m `Control.Exception.catch` \e -> id (h e) m `catch'` h = morphIO' $ \w -> w m `Control.Exception.catch` \e -> w (h e) [w = return] = join (return m `Control.Exception.catch` \e -> return (h e)) Do you see the difference? The effects are sequenced in different places. The return/join pair moves all the effects *outside* the operations such as catch... thus defeating the entire purpose of morphIO. -Isaac

On Mon, 19 Apr 2010, Isaac Dupree wrote:
Do you see the difference?
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.) Anders

On Sun, Apr 18, 2010 at 5:02 PM, wren ng thornton
Heinrich Apfelmus wrote:
Anders Kaseorg wrote:
This concept can also be generalized to monad transformers:
class MonadTrans t => MonadTransMorph t where morph :: Monad m => (forall b. (t m a -> m b) -> m b) -> t m a
[...] However, not all control operators can be lifted this way. Essentially, while you may "downgrade" an arbitrary selection of t m a values you may only promote one m a in return and all have to share the same return type a . In particular, it's not possible to implement
lift :: (Monad m, MonadTrans t) => m a -> t m a
Why not? * morph says m(t m a) is a subset of (t m a) * Monad m says we can fmap :: (a->b) -> (m a->m b) * Monad (t m) says we can return :: a -> t m a
lift ma = morph (\k -> k (fmap return ma))
Maybe something like this? lift m = morph (\k -> m >>= k . return) -- n.b., return and >>= are from different monads
Again, having m(t m a)->(t m a) is strictly more expressive than only having (m a)->(t m a) because the former may avail itself of operations/operators of t.
join . lift :: m (t m a) -> t m a
morph is more powerful than lift, but it isn't because of the type.
--
Dave Menendez

David Menendez wrote:
wren ng thornton wrote:
Heinrich Apfelmus wrote:
In particular, it's not possible to implement
lift :: (Monad m, MonadTrans t) => m a -> t m a
Why not? * morph says m(t m a) is a subset of (t m a) * Monad m says we can fmap :: (a->b) -> (m a->m b) * Monad (t m) says we can return :: a -> t m a
lift ma = morph (\k -> k (fmap return ma))
Maybe something like this?
lift m = morph (\k -> m >>= k . return) -- n.b., return and >>= are from different monads
Nice! And it's consistent with the proposed equation morph (\down -> m >>= h down) = lift m >>= morph . flip h which says that effects that happen before applying down can be lifted out of morph . Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On Wed, 14 Apr 2010, Anders Kaseorg wrote:
class Monad m => MonadMorphIO m where morphIO :: (forall b. (m a -> IO b) -> IO b) -> m a
I’d like to experimentally publish this on Hackage. Here are some questions, at least a few of which should ideally have answers before I do so: • Any ideas for what it should be named? I have to admit that I picked “morph” as a relatively generic word that doesn’t really mean anything. I wanted to call it “wrap” but discovered that MonadWrap had been taken by the monad-wrap package, which actually has a very similar goal but is slightly less general (it doesn’t support ContT). • How should the package be split up? If the same class to be useful with both mtl and transformers, one way would be to put class MonadMorphIO and its IO instance, class MonadTransMorph, and whatever useful functions like catch are wrapped with it into one package, then have two additional packages with instances for mtl and transformers, respectively. • What useful functions should be wrapped with it? Some candidates are catch, block, unblock (and friends from Control.Exception), forkIO, runInBoundThread, runInUnboundThread, unsafeInterleaveIO, withProgName, withArgs, alloca (and friends from Foreign.Marshal), withMVar, modifyMVar_, modifyMVar. Then of course there are all the functions that could be wrapped with liftIO… • Can a class like this be expressed in Haskell ’98? (But this seems to be quite difficult, and I imagine we’ll be thinking about it for a while.) • How should this relate to MonadIO? Should MonadMorphIO eventually replace MonadIO entirely? For that matter, should MonadTransMorph replace MonadTrans? • Maybe I’m thinking way too far ahead, and I should just release it now and watch from a safe distance to see what happens? Anders

On Fri, 23 Apr 2010, Anders Kaseorg wrote:
• What useful functions should be wrapped with it? Some candidates are catch, block, unblock (and friends from Control.Exception), forkIO, runInBoundThread, runInUnboundThread, unsafeInterleaveIO, withProgName, withArgs, alloca (and friends from Foreign.Marshal), withMVar, modifyMVar_, modifyMVar. Then of course there are all the functions that could be wrapped with liftIO…
On the other hand, most of the functions I listed could be easily wrapped by the user, given liftIO0 :: MonadMorphIO m => (forall b. IO b -> IO b) -> m a -> m a liftIO0 f m = morphIO $ \down -> f (down m) liftIO1 :: MonadMorphIO m => (forall b. (t -> IO b) -> IO b) -> (t -> m a) -> m a liftIO1 f g = morphIO $ \down -> f (down . g) Anders

Anders Kaseorg wrote:
On Wed, 14 Apr 2010, Anders Kaseorg wrote:
class Monad m => MonadMorphIO m where morphIO :: (forall b. (m a -> IO b) -> IO b) -> m a
I’d like to experimentally publish this on Hackage. Here are some questions, at least a few of which should ideally have answers before I do so:
• Any ideas for what it should be named? I have to admit that I picked “morph” as a relatively generic word that doesn’t really mean anything. I wanted to call it “wrap” but discovered that MonadWrap had been taken by the monad-wrap package, which actually has a very similar goal but is slightly less general (it doesn’t support ContT).
How about renaming morph to liftControl ? This makes it explicit that the point is to lift control operators.
• What useful functions should be wrapped with it? Some candidates are catch, block, unblock (and friends from Control.Exception), forkIO, runInBoundThread, runInUnboundThread, unsafeInterleaveIO, withProgName, withArgs, alloca (and friends from Foreign.Marshal), withMVar, modifyMVar_, modifyMVar. Then of course there are all the functions that could be wrapped with liftIO…
I think it's best to wrap just a few functions like catch and forkIO and then thoroughly document how to lift your own.
• How should this relate to MonadIO? Should MonadMorphIO eventually replace MonadIO entirely? For that matter, should MonadTransMorph replace MonadTrans?
It cannot be a replacement because MonadTransMorph is strictly more powerful than MonadTrans (same for IO): not every instance of MonadTrans can also be an instance of MonadTransMorph. This is why I suspect there could be something wrong with the ContT instance. Hard to tell without having a clear specification of what should be right.
• Maybe I’m thinking way too far ahead, and I should just release it now and watch from a safe distance to see what happens?
A little thought can never hurt. ;) Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On Fri, Apr 23, 2010 at 12:02 PM, Anders Kaseorg
On Wed, 14 Apr 2010, Anders Kaseorg wrote:
class Monad m => MonadMorphIO m where morphIO :: (forall b. (m a -> IO b) -> IO b) -> m a
I’d like to experimentally publish this on Hackage.
Great! Are you also planning to export the more general MonadTransMorph?: class MonadTrans t => MonadTransMorph t where morph :: Monad m => (forall b. (t m a -> m b) -> m b) -> t m a If so, it may be a good idea to also move MonadTrans from mtl and transformers to your package. Otherwise you need to depend on either one which you can't because they need to depend on you. Another solution might be to remove to MonadTrans constraint from MonadTransMorph. But that is unfortunate because any MonadTransMorph transformer is able to lift: lift m = morph (\k -> m >>= k . return) -- from: David Menendez Secondly, if we decide to move MonadIO from mtl and transformers to its own package (and not to base), I like that package to be this package. Because although MonadIO and MonadMorphIO are not equivalent they are very related.
• Any ideas for what it should be named? I have to admit that I picked “morph” as a relatively generic word that doesn’t really mean anything. I wanted to call it “wrap” but discovered that MonadWrap had been taken by the monad-wrap package, which actually has a very similar goal but is slightly less general (it doesn’t support ContT).
I also like a name that mentions "control". The recent discussion about "Monads Terminology" may also provide some inspiration: http://thread.gmane.org/gmane.comp.lang.haskell.general/17919
• How should the package be split up? If the same class to be useful with both mtl and transformers, one way would be to put class MonadMorphIO and its IO instance, class MonadTransMorph, and whatever useful functions like catch are wrapped with it into one package, then have two additional packages with instances for mtl and transformers, respectively.
Ideally mtl and transformers will depend on this package and provide the necessary instances in the same modules as where their data types are defined so avoiding orphaned instances.
• What useful functions should be wrapped with it? Some candidates are catch, block, unblock (and friends from Control.Exception), forkIO, runInBoundThread, runInUnboundThread, unsafeInterleaveIO, withProgName, withArgs, alloca (and friends from Foreign.Marshal), withMVar, modifyMVar_, modifyMVar. Then of course there are all the functions that could be wrapped with liftIO…
I definitely like to have all the Control.Exception functions available. forkIO might also be nice so that it can replace: http://hackage.haskell.org/package/forkable-monad I'm looking forward to this package! regards, Bas

On Fri, Apr 23, 2010 at 05:16:28PM +0200, Bas van Dijk wrote:
Ideally mtl and transformers will depend on this package and provide the necessary instances in the same modules as where their data types are defined so avoiding orphaned instances.
It's also possible to avoid orphan instances by having this package depend on both mtl and transformers (with qualified imports) and define instances for their types in the same module as the class.

Anders Kaseorg wrote:
• Can a class like this be expressed in Haskell ’98? (But this seems to be quite difficult, and I imagine we’ll be thinking about it for a while.)
I don't think[1] so. Fundamentally the problem is that you need to support both (things like) ReaderT and (things like) WriterT. That is, the portion of the type which is under IO (or could commutatively be made so) varies from monad to monad. Thus, it seems necessary to use extensions like rank-n (to abstract over the different structures) or MPTCs / associated types (to define relations on types). The original liftIO gets around this problem because the input is a "pure" term (wrt the monad it's being lifted into) and therefore we don't have any structure to worry about traversing/manipulating. [1] But I've been wrong before: http://www.comlab.ox.ac.uk/jeremy.gibbons/publications/fast+loose.pdf -- Live well, ~wren

On 04/10/10 11:35, Twan van Laarhoven wrote:
If MonadIO were in base, then the base library itself could also use it. For example the functions in System.IO could be lifted to work on any MonadIO monad. Whether that is a good idea is completely orthogonal to this discussion, however.
I think it is relevant to the discussion to consider whether the MonadIO class is a good idea in general -- if it's not a broad enough use, then maybe we shouldn't implicitly sanction it by putting it in 'base'. Is it mainly to make monad-transformer code more readable* by requiring fewer explicit lifts? Are there other reasons? (Pointing to example code that uses MonadIO would be a good answer.) *i've grown increasingly doubtful of the idea that more classes / less-explicit code reliably makes things more readable. (I see nothing wrong with splitting MonadIO out into a new package (besides that proliferation of packages is a bit annoying)... ) -Isaac

On Mon, Apr 12, 2010 at 8:53 PM, Isaac Dupree
On 04/10/10 11:35, Twan van Laarhoven wrote:
If MonadIO were in base, then the base library itself could also use it. For example the functions in System.IO could be lifted to work on any MonadIO monad. Whether that is a good idea is completely orthogonal to this discussion, however.
I think it is relevant to the discussion to consider whether the MonadIO class is a good idea in general -- if it's not a broad enough use, then maybe we shouldn't implicitly sanction it by putting it in 'base'. Is it mainly to make monad-transformer code more readable* by requiring fewer explicit lifts? Are there other reasons? (Pointing to example code that uses MonadIO would be a good answer.)
This is the code which prompted my original thread: http://hackage.haskell.org/packages/archive/starling/0.2.0/doc/html/Network-... So the answer to your question is 'polymorphism'.
*i've grown increasingly doubtful of the idea that more classes / less-explicit code reliably makes things more readable.
Perhaps true! At the time I wrote the above, I was frustrated with having to nail myself down to a particular technique of signaling/expressing errors, so I erred on the side of polymorphism.
(I see nothing wrong with splitting MonadIO out into a new package (besides that proliferation of packages is a bit annoying)... )
I would be for any approach which lets me use MonadIO without pulling in the mtl or transformers. Antoine

On 04/13/10 00:24, Antoine Latter wrote:
On Mon, Apr 12, 2010 at 8:53 PM, Isaac Dupree
wrote: On 04/10/10 11:35, Twan van Laarhoven wrote:
If MonadIO were in base, then the base library itself could also use it. For example the functions in System.IO could be lifted to work on any MonadIO monad. Whether that is a good idea is completely orthogonal to this discussion, however.
I think it is relevant to the discussion to consider whether the MonadIO class is a good idea in general -- if it's not a broad enough use, then maybe we shouldn't implicitly sanction it by putting it in 'base'. Is it mainly to make monad-transformer code more readable* by requiring fewer explicit lifts? Are there other reasons? (Pointing to example code that uses MonadIO would be a good answer.)
This is the code which prompted my original thread:
http://hackage.haskell.org/packages/archive/starling/0.2.0/doc/html/Network-...
So the answer to your question is 'polymorphism'.
*i've grown increasingly doubtful of the idea that more classes / less-explicit code reliably makes things more readable.
Perhaps true! At the time I wrote the above, I was frustrated with having to nail myself down to a particular technique of signaling/expressing errors, so I erred on the side of polymorphism.
Ah, I see. Once you make the erroring portion class-based, you have no choice but to also use MonadIO, because you've lost the ability to explicitly use the "IO" type. If it weren't for that issue, I'd be tempted to say: Don't show me the benefit to providers-of-interfaces (who can become more polymorphic in name, frequently while remaining equally powerful -- such as the Data.Map.lookup Maybe-vs-MonadPlus debates we've had -- where either function can be defined in terms of the other one*). Rather, I'm interested in the users of those potentially-more-general functions (both of the more-powerful and equally-powerful sorts), so that we can all get a better intuition of when/whether it's worth it to use MonadIO in interfaces. *I wonder if Conor McBride has thoughts, because I thought his thoughts on that previous debate were worth hearing
participants (15)
-
Anders Kaseorg
-
Antoine Latter
-
Bas van Dijk
-
Dan Doel
-
David Menendez
-
Edward Kmett
-
Felipe Lessa
-
Heinrich Apfelmus
-
Isaac Dupree
-
Michael Snoyman
-
Ross Paterson
-
Twan van Laarhoven
-
Tyson Whitehead
-
wren ng thornton
-
Yitzchak Gale