Saturday, March 16, 2013

mmorph-1.0.0: Monad morphisms

Several people have asked me to split off MFunctor from pipes so that they could use it in their own libraries without a pipes dependency, so today I'm releasing the mmorph library, which is the new official home of MFunctor. The upcoming pipes-3.2 release will depend on mmorph to provide MFunctor.

The mmorph library specifically targets people who make heavy use of monad transformers. Many common problems that plague users of monad transformers have very elegant solutions inspired by category theory and mmorph provides a standard home for these kinds of operations.

This post won't include examples because mmorph already features an extended tutorial at the bottom of its sole module: Control.Monad.Morph. The tutorial highlights several common use cases where the mmorph library comes in handy and I highly recommend you read it if you want to understand the concrete problems that the mmorph library solves.



Moving on up


mmorph takes several common Haskell idioms you know and love and lifts them to work on monads instead. The simplest example is a monad morphism:
{-# LANGUAGE RankNTypes, TypeOperators #-}

type m :-> n = forall a . m a -> n a
A monad morphism is a function between monads and all monad morphisms must satisfy the following two "monad morphism laws":
morph :: m :-> n

morph $ do x <- m  =  do x <- morph m
           f x           morph (f x)

morph (return x) = return x
Using the above type synonym for monad morphisms, we can simplify the type signature of hoist from the MFunctor type class:
class MFunctor t where
    hoist :: (Monad m) => (m :-> n) -> (t m :-> t n)
MFunctor is the higher-order analog of the Functor class (thus the name), and the resemblance becomes even more striking if you change the type variable names:
class MFunctor f where
    hoist :: (a :-> b) -> (f a :-> f b)
This parallel lets us reuse our intuition for Functors. An MFunctor wraps a monad in the same way that a Functor wraps a type, and MFunctors provide an fmap-like function, hoist, which modifies the wrapped monad.

If you've ever used monad transformers then you've probably already used MFunctors. Just check out the instance list for MFunctor and you'll see many familiar names:
instance MMorph  IdentityT where ...
instance MMorph  MaybeT    where ...
instance MMorph (StateT s) where ...
In fact, transformers has been carrying around type-specialized versions of hoist for years:
  • mapIdentityT is hoist for IdentityT
  • mapStateT is hoist for StateT
  • mapMaybeT is hoist for MaybeT
hoist provides a standard interface to these functions so that you can program generically over any monad transformer that implements MFunctor.


I heard you like monads


We can define a higher-order functor that wraps monads, so why not also define a higher-order monad that wraps ... monads?

It turns out that actually works!
class MMonad t where
    embed :: (Monad n) => (m :-> t n) -> (t m :-> t n)
Again, judicious renaming of type variables reveals the parallel to the Monad class:
class MMonad m where
    embed :: (Monad b) => (a :-> m b) -> (m a :-> m b)
embed is just the higher-order cousin of (=<<)! Many monad transformers have sensible definitions for embed:
instance               MMonad IdentityT   where ...
instance               MMonad MaybeT      where ...
instance (Monoid w) => MMonad (WriterT w) where ...
But wait! Where is return? Well, what type would we expect the higher-order return to have?
??? :: m :-> t m
Well, if we expand out the definition of (:->), we get:
??? :: m a -> t m a
Why, that is just the signature for lift!

But it's not enough for it to just have the right shape of type. If it's really part of a higher-order monad, then lift and embed must obey the monad laws:
-- m >>= return = m
embed lift m = m

-- return x >>= f = f x
embed f (lift x) = f x

-- (m >>= f) >>= g = m >>= (\x -> f x >>= g)
embed g (embed f m) = embed (\x -> embed g (f x)) m
... and all the MMonad instances do satisfy these laws!


Functor design pattern


The mmorph library represents a concrete example of the functor design pattern in two separate ways.

First, the monad morphisms themselves define functors that transform Kleisli categories, and the monad morphism laws are actually functor laws:
morph :: forall a . m a -> n a

(morph .) (f >=> g) = (morph .) f >=> (morph .) g

(morph .) return = return
... so you can think of a monad morphism as just a principled way to transform one monad into another monad for compatibility purposes.

Second, the hoist function from MFunctor defines a functor that transforms monad morphisms:
hoist (f . g) = hoist f . hoist g

hoist id = id
... so you can think of hoist as just a principled way to transform one monad morphism into another monad morphism for compatibility purposes.

The mmorph library is a concrete example of how functors naturally arise as compatibility layers whenever we encounter impedance mismatch between our tools. In this case, we have an impedance mismatch between our monad transformers and we use functors to bridge between them so they can seamlessly work together.

7 comments:

  1. I'm confused by the second law. How is `morph (return x)` a law? Do you mean `morph (return x) = return x`?

    ReplyDelete
    Replies
    1. Yeah, that was a mistake. I did mean `morph (return x) = return x`. I fixed it.

      Delete
  2. Also `(morph .) return` should be `(morph .) return = return`.

    Thanks for a nice library!

    ReplyDelete
    Replies
    1. You're welcome! Thanks for catching that. Now that's fixed, too.

      Delete
  3. This is neat, thanks for the hard work!

    ReplyDelete
  4. Have you read "Monads, Zippers and Views: Virtualizing the Monad Stack" by Schrijvers and Oliveira? It seems like your "hoist" is exactly their "tmap." I wonder if you think one could use mmorph to implement the same monad operations they describe in their paper?

    ReplyDelete
  5. I skimmed it once a long time ago back when I was learning monad transformers for the first time (it was way over my head back then). Having now read it again I see that `mmorph` basically corresponds to sections 4 and 5 of their paper. The idea is that the combination of `hoist` and `lift` acts like their structural mask (and they use `view`/`tmap`, but it's still the same basic idea).

    For example, if you have a global transformer stack of type:

    total :: t1 (t2 (t3 (t4 m))) r

    ... but you want to ignore layers t1 and t3. Then what you do is write a computation that assumes that only layers t2 and t4 are present:

    sub :: t2 (t4 m) r

    ... then when you are done you can merge it into the global transformer stack using `hoist` and `lift`:

    (lift . hoist lift) sub :: t1 (t2 (t3 (t4 m))) r

    This lets you write `sub` in such a way that it ignores layers it does not need, and then the client can worry about getting it to unify with other monad layers through judicious use of `lift` and `hoist`. Those `lift`s and `hoist` are basically the "structural mask" they proposed.

    However, there are several things in that paper that `mmorph` cannot do. For example, you cannot do bidirectional views, sophisticated liftings (of the kind described in section 6), or nominal liftings.

    Thanks for bringing that paper to my attention. Now I see that there is prior art in the literature for `mmorph`. Neat! :)

    ReplyDelete