Stacking Monads can be somewhat confusing to get your head around. While looking around for a decent example, I came across this Gist by Decoherence on how to combine a ReaderT with a WriterT over some Monad.

I needed to use this stack as I was working with the IO Monad and needed some way to capture the outcomes of a computation (via a Writer) and also needed to supply the initial inputs (via a Reader).

While Reader and Writer Monads on their own seem easy to use, it can be somewhat daunting to try and figure out how to combine the transformer variations of these Monads over some other Monad.

Say Monad one more time

I’m documenting my findings on how to use this stack here for anyone who might be also struggling to figure out how all this stuff hangs together. It is also for my future-self who might need a quick refresher.

Reader and ReaderT

Let’s start by looking at the type signature for the Reader Monad:

r -> a

The Reader Monad when given some resource, r from the environment will return a result of a.

The type variables defined are as follows:

  • r = resource from the environment
  • a = value returned

Next lets have a look at the type signature for a ReaderT Monad Transformer (MT):

newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a }

This is less clear than the definition of the Reader Monad. As we’ll see below they are essentially very similar.

The type variables defined are as follows:

  • r = resource from the environment
  • m = the resulting Monad
  • a = value returned in the Monad

The ReaderT MT has one extra type variable m which is a Monad. If we examine the ReaderT constructor we can see that it encapsulates a type very similar to that of the Reader Monad:

r -> m a -- ReaderT MT
r ->   a -- Reader Monad

The ReaderT MT is simply a Reader Monad whose result is returned within another Monad. More on that later. Hopefully the connection between the Reader Monad and the Reader MT is clearer.

When we see a ReaderT r m a we can mentally substitute it with a function of the type:

r -> m a

And when we see a function of the type r -> m a we can mentally substitute it with:

ReaderT r m a

Depending on the situation it might be easier to think in one of the above versions of the ReaderT MT.

Given a ReaderT r m a we can unwrap its value via the runReaderT method:

runReaderT :: ReaderT r m a -> r -> m a

Also given a simple Reader Monad (r -> a) we can lift it into a ReaderT MT with the reader or the asks function:

reader,asks :: Monad m => (r -> a) -> ReaderT r m a

Also note that ReaderT r m is a Monad if m is a Monad:

Monad m => Monad (ReaderT r m)

This is important to know when using do notation with the ReaderT MT as each bind operation will result in a ReaderT r m and not a ReaderT:

someFunc :: ReaderT r m a
someFunc = do
    r <- ask
    return a -- this will be returned into ReaderT r m

If you need to wrap a value within a ReaderT MT use:

ReaderT \r -> -- your value of (m a)

This might all seem very confusing at the moment. These are different ways of lifting values into the transformer stack at different points. Once you start using the ReaderT MT this will become clearer.

Some other useful functions that work with the ReaderT MT are:

  • ask - to retrieve the supplied resource
ask :: Monad m => ReaderT r m r
  • local - to map a function on the resource before using it:
local :: (r -> r) -> ReaderT r m a -> ReaderT r m a
  • mapReaderT - to change all components of the ReaderT MT except the input type (the inner Monad and result type):
mapReaderT :: (m a -> n b) -> ReaderT r m a -> ReaderT r n b

Writer and WriterT

As we’ve not looked at the definitions of the Writer Monad and the WriterT MT let’s do that now. The Writer Monad is defined as:

(a, w)

The type variables defined are:

  • a = return value
  • w = log value (which has to be an Monoid)

The Writer Monad will return a pair of values; a result a along with an accumulated log w.

The WriterT MT is defined as:

newtype WriterT w m a = WriterT { runWriterT :: m (a, w) }

where the type variables defined are:

  • a = return value
  • m = the resulting Monad
  • w = log value (which has to be an Monoid)

Both a and w are returned as a pair within the Monad m.

The WriterT constructor encapsulates:

m (a, w)

It’s basically a Writer Monad within another Monad m:

  (a, w) -- Writer Monad
m (a, w) -- WriterT MT

Some other useful functions that work with the WriterT MT are:

  • runWriterT - to unwrap the value of a WriterT MT and return the result and the log:
runWriterT :: WriterT w m a -> m (a, w)
  • execWriterT - to unwrap the value of a WriterT MT and return only the log:
execWriterT :: Monad m => WriterT w m a -> m w
  • tell - to write a log entry into the WriterT MT:
tell :: Monad m => w -> WriterT w m ()
  • listen - to change the result to include the log:
listen :: Monad m => WriterT w m a -> WriterT w m (a, w)
  • pass - to run a function on the log to update it:
pass :: Monad m => WriterT w m (a, w -> w) -> WriterT w m a
  • mapWriterT - to change all components of the WriterT MT (the inner Monad, result and log type):
mapWriterT :: (m (a, w) -> n (b, w’)) -> WriterT w m a -> WriterT w’ n b

MonadTrans

Let’s also have a look at the MonadTrans typeclass. It defines one function called lift:

lift :: Monad m => m a -> t m a

that lifts a Monad into a MT. We can use this function to insert a Monad into a given transformer stack.

A ReaderT WriterT example

Phew! We’ve just had a whirlwind tour of some typeclasses and related functions. Now let’s have a look at an example of using a ReaderT/WriterT transformer stack.

Say we had some configuration about an external service, like its host and port. We might use a Reader Monad to supply that configuration to the program.

Let’s start by defining a type alias to a Map of String keys and values:

import qualified Data.Map.Lazy as M

type Config = M.Map String String

Let’s also define a serverConfig function to return our populated configuration from a list of key-value pairs:

serverConfig :: Config
serverConfig = M.fromList [("host", "localhost"), ("port", "7654")]

Let’s definite a function to read the host:

getHost :: Reader Config (Maybe String)

Given a Config this function will return the host name in a Just if present, or a Nothing if not.

It would could be implemented as:

getHost :: Reader Config (Maybe String)
getHost = do
  config <- ask
  return (Map.lookup "host" config)

First, the getHost function requests the Config instance from the environment using the ask function. It then looks up the “host” key from that config. Finally it lifts the Maybe value returned from the lookup function into the Reader Monad using the return function.

Let’s define a function to read the port:

getPort :: Reader Config (Maybe Int)

It would could be implemented as:

getPort :: Reader Config (Maybe Int)
getPort = do
  config <- ask
  return (Map.lookup "port" config >>= readMaybe)

This function is similar to getHost with the additional bind (>>=) operation to join together the value read from lookup with readMaybe. readMaybe tries to parse a String into a value of type Int in this case. If it successfully parses the value it returns a (Just Int) or if it fails it returns a Nothing. readMaybe is defined as:

readMaybe :: Read a => String -> Maybe a

Also notice that we used a Reader Monad as opposed to a ReaderT MT to read both the host and port. Since the Reader Monad and the ReaderT MT are very similar we can easily convert between them. Why didn’t we use a ReaderT MT directly to read the configuration? We could have, but the ReaderT MT requires an inner Monad m:

ReaderT r m a

and we haven’t decided on what m is at the moment. I’ll demonstrate how we could have directly used a ReaderT MT to implement getHost and getPort later on.

Now that we’ve written functions to read the host and port, lets go ahead and use those values in a ReaderT MT along with a WriterT MT to log out the values we received from the configuration:

getConfig :: ReaderT Config (WriterT String IO) ()

Given a Config type as an input, the result returned will be in a WriterT MT with a log type of String with an inner Monad of IO and a value of unit () returned within IO. That sounds more complicated than it really is.

It’s implemented as:

getConfig :: ReaderT Config (WriterT String IO) ()
getConfig = do
  hostM <- fromReader getHost
  portM <- fromReader getPort
  let host = maybe "-" id hostM
      port = maybe "-" show portM
  _ <- log "\nConfig"
  _ <- log "\n======"
  _ <- log (printf "\nhost: %s" host)
  _ <- log (printf "\nport: %s" port)
  return ()

Let’s delve into the implementation of getConfig. The first two lines read the host and port into Maybe values from the configuration:

  hostM <- fromReader getHost
  portM <- fromReader getPort

The next two lines covert the Maybe values for host and port into their String equivalents:

  let host = maybe "-" id hostM
      port = maybe "-" show portM

The next four lines write String values to the log in order:

  _ <- log "\nConfig"
  _ <- log "\n======"
  _ <- log (printf "\nhost: %s" host)
  _ <- log (printf "\nport: %s" port)

and the final line returns a Unit result into the ReaderT r m Monad:

return ()

which in this case is the ReaderT (WriterT String IO) Monad.

Let’s look at the type definition of the fromReader function:

fromReader :: Monad m => Reader r a -> ReaderT r m a

fromReader converts a Reader Monad to a ReaderT MT. It is implemented as:

fromReader :: Monad m => Reader r a -> ReaderT r m a
fromReader = reader . runReader

The runReader function is defined as:

runReader :: Reader r a -> r -> a

and unwraps the Reader Monad to a function (r -> a). The reader function (as defined previously) lifts a function from (r -> a) into the ReaderT MT. This seems like unnecessary work and ideally there should be an in-built function that does this for us.

Next let’s have a look at the log function:

log :: (Monad m, MonadTrans t, Monoid w) => w -> t (WriterT w m) ()
log = lift . tell

From the type definition of tell:

tell :: Monad m => w -> WriterT w m ()

we can see that we almost get the result we want:

w -> WriterT w m ()

We just need to lift the WriterT w m Monad into a Monad Transformer t and we can do that with the lift defined previously:

lift :: Monad m => m a -> t m a

which gives us:

w -> WriterT w m () -- tell

m a -> t m a -- lift
-- replacing m with (WriterT w m)
(WriterT w m) a -> t (WriterT w m) a
-- replacing a with ()
(WriterT w m) () -> t (WriterT w m) ()

-- combining lift . tell
w -> t (WriterT w m) ()

We can see that we are lifing some log w into a transformer stack t through the WriterT w m Monad.

We’ve come a long way and we’ve got everything setup as needed. The only thing left to do is run the transformer stack and reap our rewards. We can do that with the readWriteConfig function:

readWriteConfig :: IO ()
readWriteConfig = execWriterT (runReaderT getConfig serverConfig) >>= putStrLn

When running the stack, it is run from outside-in. So given a ReaderT (WriterT String m) a, we:

  1. Run the ReaderT MT:
r -> m a

with runReaderT. This returns the result a in the inner Monad m which is a WriterT String m. Substituting the IO Monad for m and Unit for a returns a WriterT String IO (). We don’t care about the result of a - only the log.

  1. Run the WriterT MT:
m (a, w)

with execWriterT. This returns the log w in the inner Monad m which is an m w. Substituting the IO Monad for m and String for w, returns an IO String.

  1. Binding through from IO String to putStrLn gives us an IO (). The final output of running the above is:
Config
======
host: localhost
port: 7654

Using ReaderT instead of Reader

I previously mentioned that we could have written the getHost and getPort functions with a ReaderT MT instead of a Reader Monad. Here’s how we’d do that:

getHost2

getHost2 :: Monad m => ReaderT Config m (Maybe String)
getHost2 = -- same as getHost

Notice that the only difference between getHost and getHost2 is the addition of a new type variable m which is a Monad:

getHost  ::            Reader  Config   (Maybe String) -- Reader Monad
getHost2 :: Monad m => ReaderT Config m (Maybe String) -- ReaderT MT

And since we are working with Monads in both cases, the implementation code remains unchanged! So just by changing the type definition of the getConfig method we can go from a Reader Monad to a ReaderT MT!

getPort2

getPort2 :: Monad m => ReaderT Config m (Maybe Int)
getPort2 = -- same as getPort

getConfig2

getConfig2 :: ReaderT Config (WriterT String IO) ()
getConfig2 = do
  hostM <- getHost2 -- no need to call fromReader
  portM <- getPort2 -- no need to call fromReader
  ... -- same as getConfig

We can see that this solution is a lot easier with less work to do. We just needed to add a Monad type constraint to the getHost2 and getPort2 functions. We also have no need for the fromReader function which is a bonus! We can also call the readWriteConfig function with getConfig2 instead of getConfig and it all works:

readWriteConfig2

readWriteConfig2 :: IO ()
readWriteConfig2 = execWriterT (runReaderT getConfig2 serverConfig) >>= putStrLn

The complete Solution

module Config (readWriteConfig) where

import Text.Printf (printf)
import Control.Monad.IO.Class
import Control.Monad.Trans.Class
import Control.Monad.Trans.Reader
import Control.Monad.Trans.Writer.Lazy
import qualified Data.Map.Lazy as Map
import Data.List (intercalate)
import Data.Functor.Identity (Identity, runIdentity)
import Text.Read (readMaybe)
import Prelude hiding (log)

type Config = Map.Map String String

serverConfig :: Config
serverConfig = Map.fromList [("host", "localhost"), ("port", "7654")]

-- variation with Reader

getHost :: Reader Config (Maybe String)
getHost = do
  config <- ask
  return (Map.lookup "host" config)

getPort :: Reader Config (Maybe Int)
getPort = do
  config <- ask
  return (Map.lookup "port" config >>= readMaybe)

fromReader :: Monad m => Reader r a -> ReaderT r m a
fromReader = reader . runReader

log :: (Monad m, MonadTrans t, Monoid w) => w -> t (WriterT w m) ()
log = lift . tell

getConfig :: ReaderT Config (WriterT String IO) ()
getConfig = do
  hostM <- fromReader getHost
  portM <- fromReader getPort
  let host = maybe "-" id hostM
      port = maybe "-" show portM
  _ <- log "\nConfig"
  _ <- log "\n======"
  _ <- log (printf "\nhost: %s" host)
  _ <- log (printf "\nport: %s" port)
  return ()

readWriteConfig :: IO ()
readWriteConfig = execWriterT (runReaderT getConfig serverConfig) >>= putStrLn

-- variation with ReaderT

getHost2 :: Monad m => ReaderT Config m (Maybe String)
getHost2 = do
  config <- ask
  return (Map.lookup "host" config)

getPort2 :: Monad m => ReaderT Config m (Maybe Int)
getPort2 = do
  config <- ask
  return (Map.lookup "port" config >>= readMaybe)

getConfig2 :: ReaderT Config (WriterT String IO) ()
getConfig2 = do
  hostM <- getHost2
  portM <- getPort2
  let host = maybe "-" id hostM
      port = maybe "-" show portM
  _ <- log "\nConfig"
  _ <- log "\n======"
  _ <- log (printf "\nhost: %s" host)
  _ <- log (printf "\nport: %s" port)
  return ()

readWriteConfig2 :: IO ()
readWriteConfig2 = execWriterT (runReaderT getConfig2 serverConfig) >>= putStrLn

A Tale of At Least Two Monads

A Monad is based on a type constructor:

(* -> *)

which has one type hole; it creates a type when given a type. A simple example is the Maybe Monad:

Maybe :: * -> *

While we can create a Monad instance for the Maybe type constructor, a specific Maybe instance like Maybe String can’t have one because it has no type holes:

 Maybe         :: * -> *
(Maybe String) ::      * -- no type hole

Each Monad Transformer is composed of at least two Monads. If we take ReaderT MT as an example, we have its definition as:

ReaderT r m a

where ReaderT r m is a Monad and m is also a Monad. If you stack Monads, in the m type variable as with a WriterT for example:

ReaderT r (WriterT w m) a

then ReaderT r (WriterT w m) is a Monad, WriterT w m is a Monad and m is a Monad. Talk about Monad overload!

Mind Blown

Decoherence’s Example

What we’ve learned so far will help us understand the example from Decoherence I mentioned at the start of this post.

We start off by defining a data type for a Person:

data Person = Person { name :: String } deriving Show

We then create a few specific Person instances:

alex :: Person
alex = Person "Alex Fontaine"

philip :: Person
philip = Person "Philip Carpenter"

kim :: Person
kim = Person "Kim Lynch"

followed by a peopleDb function that returns a list of Person instances:

peopleDb :: [Person]
peopleDb = [alex, philip, kim]

We then define a process function as:

process :: ReaderT Person (WriterT String IO) ()

and a process’ function as:

process' :: ReaderT Person (WriterT String IO) String

The main difference between the above functions is that one returns a Unit return type and the other returns a String, respectively. Given that the ReaderT MT stack is almost the same as that in the previous example, it should be fairly easy to implement the above functions.

The process function is implemented as:

process :: ReaderT Person (WriterT String IO) ()
process = do
  _ <- log $ "Looking up Person. "
  Person p <- ask
  _ <- log $ printf "Found person: %s. " p
  (liftIO . putStrLn) p

We’ve not seen the liftIO function before. It’s defined in the MonadIO typeclass as:

liftIO :: IO a -> m a

which just lifts a value from the IO Monad into another Monad. In the above example, liftIO will lift a Unit value from the IO Monad (putStrLn p), into the ReaderT Person (WriterT String IO) Monad.

The process’ function is implemented as:

process' :: ReaderT Person (WriterT String IO) String
process' = do
  _ <- log "Looking up Person... "
  Person p <- ask
  _ <- log $ printf "Found person: %s. " p
  return p

Let’s define a function to run the transformer stack:

readWritePeople :: IO ()
readWritePeople = do

Let’s start by running the process function with a Person instance:

  result1 <- runWriterT (runReaderT process alex) -- :: ((), String)
  _ <- (putStrLn . snd) result1

Next let’s Run the process’ function with a Person instance:

  result2 <- runWriterT (runReaderT process' alex) -- :: (String, String)
  _ <- (putStrLn . fst) result2
  _ <- (putStrLn . snd) result2

Traversable

Before we look at the next invocation let’s look at the definition of the mapM function. The mapM function maps each element of a structure to a monadic action, evaluates these actions from left to right, and collects the results.

mapM :: Monad m => (a -> m b) -> t a -> m (t b)

t is the Traversable typeclass which has a Functor and Foldable constraint:

class (Functor t, Foldable t) => Traversable t where

There is also a similarly named mapM_ function:

mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()

which just differs from mapM in its result:

mapM  :: (a -> m b) -> t a -> m (t b)
mapM_ :: (a -> m b) -> t a -> m () -- only performs a side effect

which it discards (returns Unit). This is useful when you don’t care about the return value and just want to perform some side effect.

Some other interesting functions on the Traversable typeclass are:

  • traverse - has the same definition as mapM where the container is an Applicative instead of a Monad:
traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
mapM     :: Monad       m => (a -> m b) -> t a -> m (t b)
  • sequenceA - Evaluate each action in the structure from left to right, and and collect the results.
sequenceA :: Applicative f => t (f a) -> f (t a)
  • sequence - Evaluate each monadic action in the structure from left to right, and collect the results.
sequence   :: Monad m      => t (m a) -> m (t a)

sequence and sequenceA are also Monadic and Applicative variants of each other:

sequenceA  :: Applicative f => t (f a) -> f (t a)
sequence   :: Monad m       => t (m a) -> m (t a)

There are also sequence_ and sequenceA_ variants that discard the results of the action.

Running ReaderT MT with Multiple Inputs

Let’s use mapM to run our ReaderT stack with multiple input values:

  result3 <- runWriterT (mapM (runReaderT process') peopleDb) -- :: ([String], String)

  let people = fst result3
      log    = snd result3

  _ <- putStrLn "\n\nReaderT values:\n"
  _ <- mapM_ putStrLn people
  _ <- putStrLn "\nWriterT log:\n"

The mapM function is run as follows:

  1. Each runReaderT process’ is supplied a Person from the peopleDb function, which then returns a WriterT String IO String.
  2. These results are then collected as a WriterT String IO [String].

Here’s how we derive the result by replacing each type parameter with the actual types:

mapM :: (a -> m b) -> t a -> m (t b)
-- replacing a with Person:
mapM    (Person -> m b) t Person  -> m (t b)
-- replacing t with []:
mapM    (Person -> m b) [Person]  -> m [b]
-- replacing m (the Monad) with WriterT String IO
(Person -> WriterT String IO b) -> [Person] -> WriterT String IO [b]
-- replacing b with String
(Person -> WriterT String IO String) -> [Person] -> WriterT String IO [String]
-- which returns the this result:
WriterT String IO [String]

The final output is:

Alex Fontaine
Looking up Person. Found person: Alex Fontaine.
Alex Fontaine
Looking up Person... Found person: Alex Fontaine.


ReaderT values:

Alex Fontaine
Philip Carpenter
Kim Lynch

WriterT log:

Looking up Person... Found person: Alex Fontaine. Looking up Person... Found person: Philip Carpenter. Looking up Person... Found person: Kim Lynch.

I hope this walk-through has made using Monad Transformers a little more approachable.

The code for these examples can be found Github.

References

  1. use-readert-maybe-or-maybet-reader
  2. Monad_transformers
  3. how-to-play-with-control-monad-writer-in-haskell