Jakub Arnold's Blog


Building Monad Transformers - Part 1

In this article we’ll focus on building our own monad transformers. We’ll start out with an example code and improve it by building a simple wrapper over IO (Maybe a).

The following example is really simple, but I’m sure you can imagine doing something similar in your own application. The findById method is there just to simulate a database query that might not find a result.

data User = User deriving Show

findById :: Int -> IO (Maybe User)
findById 1 = return $ Just User
findById _ = return Nothing

findUsers :: Int -> Int -> IO (Maybe (User, User))
findUsers x y = do
    muser1 <- findById x

    case muser1 of
        Nothing -> return Nothing
        Just user1 -> do
            muser2 <- findById y

            case muser2 of
                Nothing -> return Nothing
                Just user2 -> do
                    return $ Just (user1, user2)

While there’s nothing bad about case statements with pattern matching I’m sure we can all agree that this approach can easily blow out of proportions.

One solution that won’t work all the time might be to fetch both of the users at the same time, which would allow us to make use of the Maybe monad. If our findById function didn’t do any side effects, we could’ve written this.

findById :: Int -> Maybe User
findById 1 = Just User
findById _ = Nothing

loadUsers :: Maybe (User, User)
loadUsers = do
    user1 <- findById 1
    user2 <- findById 2
    return (user1, user2)

Because Maybe is implemented in a way that it stops evaluating when it hits on Nothing we get the behavior we intended without pattern matching. If one of our findById fails to return a user, the whole function will return a Nothing.

Unfortunately the act of finding a user needs to reach out to the real world, which forces the IO monad upon us, making this approach impossible. We somehow need to be able to teach IO the notion of failure.

Wrapping IO in MaybeIO

Let’s introduce a new monad which will simply wrap our IO computations into a Maybe.

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

The next step is to make MaybeIO into a Monad, which will allow us to use it inside a do block, but first things first. The next version of GHC (7.10) will require every Monad to also be an Applicative, which also means that every Monad must be a Functor. We’ll follow this an start out with a Functor instance.

instance Functor MaybeIO where
    fmap f m = undefined

We’ll use type holes to hint us in while implementing these instances. First let’s recap the type of fmap, which is (a -> b) -> f a -> f b, which means we have a function f :: a -> b and a functor value m :: f a, or specifically m :: MaybeIO a.

Before we can do anything to the m we need to unwrap MaybeIO to get to the insides. We’ll use pattern matching to do that since it’s more concise than using runMaybeIO.

instance Functor MaybeIO where
    fmap f (MaybeIO m) = undefined

We only have two things available to us, the function f :: a -> b which only works on the type a, and the fact that both Maybe and IO are also Functor instances, which means we can use fmap to reach deep into the Maybe (IO a) to apply our function f to get the result.

Here comes a little trick, since fmap can also be thought of as (a -> b) -> (f a -> f b). If we compose fmap with fmap, it gives us exactly what we need, a way to reach two functors deep to apply a function.

λ> :t fmap.fmap
:: (Functor f, Functor g) => (a -> b) -> f (g a) -> f (g b)

Substituting our types we get the following.

fmap.fmap :: (a -> b) -> (IO (Maybe a) -> IO (Maybe b))

We are not there quite yet, let’s see what happens if we use this approach to implement the Functor instance.

instance Functor MaybeIO where
    fmap f (MaybeIO m) = (fmap.fmap) f m

-- Couldn't match type ‘Maybe’ with ‘MaybeIO’

We’re returning the wrong type! The original value passed in was MaybeIO a and we’re returning IO (Maybe b) instead of MaybeIO b. Let’s add a type hole to make this crystal clear.

instance Functor MaybeIO where
    fmap f (MaybeIO m) = _ $ (fmap.fmap) f m

-- Found hole ‘_’ with type: Maybe (IO b) -> MaybeIO b

Now remember how in the beginning we said we’ll be wrapping the IO (Maybe a) into a MaybeIO? We can do that using the constructor of MaybeIO!

instance Functor MaybeIO where
    fmap f (MaybeIO m) = MaybeIO $ (fmap.fmap) f m

There you go, a Functor instance for MaybeIO.

Applicative instance for MaybeIO

The next step is to implement an Applicative instance for our MaybeIO wrapper. Here’s how the Applicative class looks in case you forgot.

class Applicative m where
    pure :: a -> m a
    (<*>) :: m (a -> b) -> m a -> m b

In terms of our MaybeIO the types would look as following.

pure :: a -> MaybeIO a
(<*>) :: MaybeIO (a -> b) -> MaybeIO a -> MaybeIO b

Implementing pure is simple, we just need to wrap a given value into a minimal context. Since both Maybe and IO are an instance of Applicative, we can use their pure much as we used fmap when implementing the Functor instance (don’t forget to import Control.Applicative.)

instance Applicative MaybeIO where
    pure = MaybeIO . pure . pure

We could’ve also written this more explicitly using Just instead of pure for wrapping the value in a Maybe.

instance Applicative MaybeIO where
    pure = MaybeIO . pure . Just

But moving on, now comes the hard part, implementing <*>. This is probably the hardest part of the whole article, so don’t worry if it seems a bit complicated. First we need to pattern match to get rid of the MaybeIO wrapper, and then we also need to wrap the value on the right hand side in the last step.

instance Applicative MaybeIO where
    pure = MaybeIO . pure . Just
    MaybeIO f <*> MaybeIO m = MaybeIO $ _

-- Found hole ‘_’ with type: IO (Maybe b)

The type hole tells us that we need to somehow get to a IO (Maybe b) with the given IO (Maybe (a -> b)) and IO (Maybe a). This seems like a typical reach into a box/context and apply a function kind of problem, and it is, but we do need to do something which isn’t so apparent at first.

Both Maybe and IO are an instance of Applicative, which means we need to somehow use <*> to apply the boxed function to the boxed value (pardon me for saying boxed here, but it just seems like the right analogy here.)

The problem is that we can only use <*> to apply a function nested one level deep, since the type is m (a -> b) -> m a -> m b. Knowing that <*> is a two argument function, meaning we can’t use simple ., we need to look into the documentation for Applicative and find the function liftA2, works just like fmap on functors, but for two argument functions.

λ> :t liftA2
:: Applicative f => (a -> b -> c) -> f a -> f b -> f c

If we combine these two together we do get exactly what we need, a function which takes two arguments, where first one is a function nested in two applicatives, and a value, and applies the function to that value.

λ> :t liftA2 (<*>)
:: (Applicative f, Applicative g) =>
     f (g (a -> b)) -> f (g a) -> f (g b)

Let’s substitute our types once again to see how this exactly matches to what we need.

liftA2 (<*>)
:: IO (Maybe (a -> b)) -> IO (Maybe a) -> IO (Maybe b)

We already have both of the arguments of the correct types, which means we can just apply the function to them and get our instance.

instance Applicative MaybeIO where
    pure = MaybeIO . pure . Just
    MaybeIO f <*> MaybeIO m = MaybeIO $ liftA2 (<*>) f m

In the next step we’ll move onto implementing the Monad instance. Make sure you understand what we’ve done so far.

Monad instance for MaybeIO

Now comes the final step that we’ve been waiting for, implementing a Monad instance for our MaybeIO wrapper. As we did before, here’s how the Monad class looks.

class Monad m where
    return :: a -> m a
    (>>=) :: m a -> (a -> m b) -> m b

We can already see that return will be exactly the same as pure for our Applicative, so let’s do that first.

instance Monad MaybeIO where
    return = pure

Next comes the implementation of >>= or bind. First the initial structure

instance Monad MaybeIO where
    return = pure
    MaybeIO m >>= f = MaybeIO $ _

We have a value of type m :: IO (Maybe a) and a function that we need to apply to the inner a which has a type f :: a -> MaybeIO b. We can use >>= to get to the value inside the IO monad.

instance Monad MaybeIO where
    return = pure
    MaybeIO m >>= f = MaybeIO $ m >>= \x -> _

This leaves us with x :: Maybe a, which is just one pattern match away from the final solution.

instance Monad MaybeIO where
    return = pure
    MaybeIO m >>= f = MaybeIO $ m >>= \x -> case x of
        Nothing -> return $ Nothing
        Just val -> runMaybeIO $ f val

A very important thing to note here is that in the case of Just val we need to unwrap the MaybeIO using runMaybeIO. One might think that we could instead write it like this.

instance Monad MaybeIO where
    return = pure
    MaybeIO m >>= f = m >>= \x -> case x of
        Nothing -> MaybeIO $ return $ Nothing
        Just val -> f val

-- Couldn't match type ‘IO’ with ‘MaybeIO’

The problem here is that m >>= \x -> ... must have a return value of IO, but we’re trying to return MaybeIO. This is why we need to unwrap the result of f val and then wrap it again after doing >>=, as we did in the previous example.

Using MaybeIO to cleanup our initial example

We manage to build ourselves a monad which combines the effects of IO and Maybe together, which means we can use it to represent IO computations which can fail. This is perfect for our initial example which uses findById :: Int -> IO (Maybe User).

Since the type of our computation is MaybeIO we need to wrap the findById function to make use of the monad instance for MaybeIO.

smartFindUsers :: Int -> Int -> MaybeIO (User, User)
smartFindUsers x y = do
    user1 <- MaybeIO $ findById x
    user2 <- MaybeIO $ findById y

    return (user1, user2)

We can even go one step further and keep the original return value of findUsers IO (Maybe (User, User)) by unwrapping the MaybeIO.

smartFindUsers :: Int -> Int -> IO (Maybe (User, User))
smartFindUsers x y = runMaybeIO $ do
    user1 <- MaybeIO $ findById x
    user2 <- MaybeIO $ findById y

    return (user1, user2)

Now let’s go ahead and test this in GHCi to make sure we didn’t break anything.

λ> smartFindUsers 1 1
Just (User,User)

Our new version works exactly the same as the old one, but without the necessary error handling boilerplate. Much like monads allow you to capture control flow patterns, you can use monad transformers to add additional control flow to your existing monads without sacrificing readability of your code.

The next step is to make our MaybeIO into an actual transformer by swapping IO for any Monad.

Generalizing MaybeIO to MaybeT

The real monad transformers you’ll encounter in the world of Haskell are a bit more generic than the one we just implemented. Instead of hard-coding the IO monad we’ll pass it in as a type parameter, resulting in the following definition of MaybeT.

newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) }

There aren’t any significant changes, we just introduced a new type parameter which will be the monad we’re wrapping. Since everything else remains almost exactly the same, I’ll just show the Monad implementation here.

newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) }

instance Monad m => Monad (MaybeT m) where
    return = MaybeT . return . Just
    MaybeT m >>= f = MaybeT $ do value <- m
                                 case value of
                                     Nothing -> return Nothing
                                     Just x -> runMaybeT $ f x

The only notable thing here is that our type parameter m is restricted to be a Monad as well, since we’re only going to be wrapping monads.

Our findUsers function will be exactly the same, we’ll just need to swap runMaybeIO for runMaybeT.

transformerFindUsers :: Int -> Int -> IO (Maybe (User, User))
transformerFindUsers x y = runMaybeT $ do
    user1 <- MaybeT $ findById x
    user2 <- MaybeT $ findById y

    return (user1, user2)

Just to make it crystal clear what’s going on here, the function without using runMaybeT would look as follows.

wrappedFindUsers :: Int -> Int -> MaybeT IO (User, User)
wrappedFindUsers x y = do
    user1 <- MaybeT $ findById x
    user2 <- MaybeT $ findById y

    return $ Just (user1, user2)

We can even introduce a type alias to have something called MaybeIO using the MaybeT transformer.

type MaybeIO a = MaybeT IO a

This is actually how the well known monads such as Reader, Writer and State are defined. They’re just type synonyms for the respective transformers using the Identity monad.

type Reader r = ReaderT r Identity
type Writer w = WriterT w Identity
type State s = StateT s Identity

If you’re interested in learning more about the Identity monad and how it can be used in some more advanced settings, take a look at my Introduction to Lenses article where it’s explained step by step in great detail.

This concludes the first article in the series on Monad Transformers. Next time we’ll take a look at how we can stack one transformer onto another and introduce the MonadTrans and MonadIO type classes.

Related
Haskell