MonadMorphIO [Re: Move MonadIO to base]

Bas van Dijk v.dijk.bas at gmail.com
Fri Apr 23 11:16:28 EDT 2010


On Fri, Apr 23, 2010 at 12:02 PM, Anders Kaseorg <andersk at mit.edu> 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.

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


More information about the Libraries mailing list