Monad Transformers Tutorial

From HaskellWiki
Revision as of 21:41, 7 February 2011 by Peaker (talk | contribs) (Fix kind signature. Explain the name.)
Jump to navigation Jump to search

Think about code in IO that needs to be able to break out of a loop:

forM_ [1..maxRetries] $ \i -> do
  response <- request i
  when (satisfied response) break

Reminder about "when":

when False _ = return ()
when True a = a

So, how would you implement "break"?

Another example:

do
  mc1 <- tryConnect "host1"
  case mc1 of
    Nothing -> return Nothing
    Just c1 -> do
      mc2 <- tryConnect "host2"
      case mc2 of
        Nothing -> return Nothing
        Just c2 -> do
          ..

Clearly we want something like Maybe's (>>=) here to catch the Nothing, but instead of Maybe values and functions we can combine with (>>=), we have IO (Maybe a) values. So the "trick" is to implement the Maybe monad again, this time, on IO (Maybe a) values instead of Maybe a values:

newtype MaybeIO a = MaybeIO {
   runMaybeIO :: IO (Maybe a)
}

instance Monad MaybeIO where
  return x = MaybeIO (return (Just x))
  MaybeIO action >>= f = MaybeIO $ do
    result <- action
    case result of
      Nothing -> return Nothing
      Just x -> runMaybeIO (f x)

So now we can replace the above boilerplate code with:

result <- runMaybeIO $ do
  c1 <- MaybeIO $ tryConnect "host1"
  c2 <- MaybeIO $ tryConnect "host2"
  ..

Or if the tryConnect function wrapped its result in MaybeIO then we just have to use runMaybeIO there, and that's it. What happens if we now have some "print" in between?

result <- runMaybeIO $ do
  c1 <- MaybeIO $ tryConnect "host1"
  print "Hello"
  c2 <- MaybeIO $ tryConnect "host2"
  ..

This wouldn't work, because the type of each statement in our do block is MaybeIO a and not IO a, so a (print "Hello") which is IO () cannot be put in there. This is where we want to "transform" an IO a value to a MaybeIO a value. All we have to do is convert the IO a to an IO (Maybe a) that doesn't "fail" our Maybe monad. So it just means putting a Just in there:

transformIOtoMaybeIO :: IO a -> MaybeIO a
transformIOtoMaybeIO action = MaybeIO $ do
  result <- action
  return (Just result)

And now we can do:

result <- runMaybeIO $ do
  c1 <- MaybeIO $ tryConnect "host1"
  transformIOtoMaybeIO $ print "Hello"
  c2 <- MaybeIO $ tryConnect "host2"
  ..

Now we can also break from the first example's loop!

break :: MaybeIO a
break = MaybeIO $ return Nothing

forM_ [1..maxRetries] $ \  i -> do
  response <- transformIOtoMaybeIO $ request i
  when (satisfied response) break

But, all of this code, while useful, is not in Haskell's spirit. Because MaybeIO really could work for any monad wrapping the Maybe, not just IO (Maybe a). The only IO operations all of the MaybeIO code performs is return and bind! So let's generalize our MaybeIO definition to all monads:

newtype MaybeT m a = MaybeT {
   runMaybeT :: m (Maybe a)
}
instance Monad m => Monad (MaybeT m) where
  return x = MaybeT (return (Just x))
  MaybeT action >>= f = MaybeT $ do
    result <- action
    case result of
      Nothing -> return Nothing
      Just x -> runMaybeT (f x)

That was easy! I just replaced MaybeIO with MaybeT, IO with m, and added an "m" type parameter (with Monad constraint).

transformToMaybeT :: Monad m => m a -> MaybeT m a
transformToMaybeT action = MaybeT $ do
  result <- action
  return (Just result)

Again, really easy, just syntactic replacement of IO with a type parameter. Now, this "transformToMaybeT" operation is really common, because we don't just have MaybeT, we also want EitherT (when you want to break out of the loop or fail with a result!), ContT (lets you do really crazy things), ListT and many others. All of these have in common a lift operation which is very much like "transformToMaybeT". So if we have:

transformToMaybeT :: Monad m => m a -> MaybeT m a
transformToEitherT :: Monad m => m a -> EitherT l m a

It seems we can capture this pattern with a class:

class MonadTrans t where
    lift :: (Monad m) => m a -> t m a

And now "t" is our MaybeT (of kind (* -> *) -> * -> *, i.e: two type parameters) and lift is our transformToMaybeT, so:

instance MonadTrans MaybeT where
    lift = transformToMaybeT

Why are they named Monad Transformers? Note the kind signature of instances of the MonadTrans class: (* -> *) -> (* -> *). That is, every monad transformer type constructor takes a monad (kind * -> *) as an argument, and returns a monad (also * -> *) as a result. So all Monad Transformers are basically type-functions from monad types to different monad types which have additional traits.