[Haskell-cafe] Monads from Functors

Ryan Ingram ryani.spam at gmail.com
Wed Apr 8 20:29:29 EDT 2009


On Wed, Apr 8, 2009 at 11:22 AM, Sebastian Fischer
<sebf at informatik.uni-kiel.de> wrote:
>> newtype ContT t a = ContT { unContT :: forall r . (a -> t r) -> t r }
>>
>> instance Monad (ContT t)
>>  where
>>   return x = ContT ($x)
>>   m >>= f  = ContT (\k -> unContT m (\x -> unContT (f x) k))

> Both the `mtl` package and the `transformers` package use the same
> `Monad` instance for their `ContT` type but require `t` to be an
> instance of `Monad`. Why? [^1]

You are missing one important piece of the puzzle for ContT:

> lift :: Monad m => m a -> ContT m a
> lift m = ContT $ \k -> m >>= k

This >>= is the bind from the underlying monad.  Without this
operation, it's not very useful as a transformer!

Without lift, it's quite difficult to get effects from the underlying
Applicative *into* ContT.  Similarily, your MonadPlus instance would
be just as good replacing with the "free" alternative functor:

data MPlus a = Zero | Pure a | Plus (MPlus a) (MPlus a)

and then transforming MPlus into the desired type after runContT; it's
the embedding of effects via lift that makes ContT useful.

The CPS transfrom in ContT also has the nice property that it makes
most applications of >>= in the underlying monad be right-associative.
 This is important for efficiency for some monads; especially free
monads; the free monad discussed by jcc has an O(n^2) running cost for
n left-associative applications of >>=.

  -- ryan


More information about the Haskell-Cafe mailing list