Blog Archive

Sunday, February 15, 2009

MaybeT - The CPS Version

> {-# LANGUAGE Rank2Types #-}
> import Control.Monad
I think I finally understand writing code into continuation passing style. I've understood it at an academic level for some time - but that's different from being able to write the code.

This post presents a different implementation of the Maybe monad transformer - usually presented as so:

data MaybeT m a = MaybeT {runMaybeT :: m (Maybe a)}
which can be used to add the notion of short-circuiting failure to any other monad (sortof a simpler version of ErrorT from the MTL).
I first came across MaybeT in a page on the Haskell Wiki.
This presentation of MaybeT uses the Church encoding of the data-type:
> newtype MaybeT m a = MaybeT {unMaybeT :: forall b . m b -> (a -> m b) -> m b}
Note the similarity to the Prelude function maybe. We can unwrap the transformer like so:

> runMaybeT :: Monad m => MaybeT m a -> m (Maybe a)
> runMaybeT m = unMaybeT m (return Nothing) (return . Just)
This runMaybeT should be a drop-in replacement for the old one.
The advantage here is that we can write the Monad and MonadPlus instances without calling bind or return in the underlying monad m, and without doing any case analysis on Just or Nothing values:
> instance Monad (MaybeT m) where
> return x = MaybeT $ \_ suc -> suc a
>
> m >>= k = MaybeT $ \fail suc ->
> unMaybeT m fail $ \x ->
> unMaybeT (k x) fail suc
>
> fail _ = mzero

> instance MonadPlus (MaybeT m) where
> mzero = MaybeT $ \fail _ -> fail
>
> m `mplus` n = MaybeT $ \fail suc ->
> unMaybeT m (unMaybeT n fail suc) suc
It's just a matter of threading the failure and success continuations to the right place at the right time.
To show that this is equivalent to the old implementation, here's a re-write of the old MaybeT data constructor from above:

> fromMaybe :: Monad m => m (Maybe a) -> MaybeT m a
> fromMaybe m = MaybeT $ \fail suc -> do
> res <- m
> case res of
> Nothing -> fail
> Just x -> suc x

So anything you can do with the other version, you can do with this version. And for most things it should be a drop-in replacement.

2 comments:

Edward Kmett said...

You may find that this understanding helps with the understanding of the codensity monad for a given functor.

newtype Codensity m a = Codensity { runCodensity :: forall b. (a -> m b) -> m b }

http://hackage.haskell.org/packages/archive/category-extras/0.53.5/doc/html/src/Control-Monad-Codensity.html#Codensity

Is just the 'Just' case of your MaybeT and hence, it's the equivalent encoding for IdentityT.

baileitaguchi said...

Play Blackjack (Saucify) - Mapyro
Blackjack is a popular card game played by two 화성 출장마사지 partnerships. The 안성 출장마사지 dealer plays the same cards and 경상북도 출장안마 offers 제주도 출장안마 them to the dealer, who then plays 동두천 출장샵 the

Listening:

Watching:

  • House
  • Ride Back