MonadState, MonadReader, MonadWriter, MonadIO
Technically, monad transformers are all we need to build monads that combine
different effects. However, all this lifting of functions from the underlying
monads into the transformed monad gets tedious. To make working with monad
transformers a bit easier, the standard library includes subclasses of Monad
that provide the operations we expect from reader, writer, and state monads:
class Monad m => MonadReader r m | m -> r where
ask :: m r
local :: (r -> r) -> m a -> m a
reader :: (r -> a) -> m a
class (Monoid w, Monad m) => MonadWriter w m | m -> w where
tell :: w -> m ()
listen :: m a -> m (a, w)
pass :: m (a, w -> w) -> m a
writer :: (a, w) -> m a
class Monad m => MonadState s m | m -> s where
get :: m s
put :: s -> m ()
state :: (s -> (a, s)) -> m a
Ignore the additional functions for now, as well as the weird stuff like
m -> r
in the class header. Then these definitions say that any monad that
comes equipped with ask
is a reader monad, any monad that comes equipped with
tell
is a writer monad, and any monad that comes equipped with get
and put
is a state monad.
As we will see shortly, we can easily define instances where, for example,
wrapping State
, or in fact any monad m
that is an instance of MonadState
,
in ReaderT
, WriterT
or MaybeT
gives us a monad that is once again an
instance of MonadState
. Thus, any such monad supports get
and put
directly.
To make this a little more concrete. If we build a monad
type MaybeState s = MaybeT (State s)
then this monad will automatically be an instance of MonadState
. Thus, instead
of having to lift get
and put
from State
into MaybeState
, as in
do
...
currentState <- lift get
...
we can simply write
do
...
currentState <- get
...
When only one level of lifting is involved, we could probably live with having
to use lift
explicitly, but if our State
monad is nested many levels deep in
a deep transformer stack, then simply get
surely beats
lift $ lift $ lift $ lift get
.
So let's puzzle apart the rest of these class definitions. First, in addition to
ask
, any reader monad must support two additional functions, local
and
reader
. local mod f
takes some computation f
in the reader monad and runs
it in some modified context. For example, we could have a program that has the
ability to log intermediate results of its computation. We could implement such
a program using
data LogRecord = ...
data Config = Config { loggingLevel :: Int }
type Prog = ReaderT Config (Writer [LogRecord])
program :: args -> Prog result
program = ...
Many programs that offer logging allow us to choose a logging level: 0 would
mean no logging, and higher and higher logging levels mean that more and more
detailed information is added to the log. Now, it might make sense to turn
logging off in part of our program no matter the logging level chosen by the
user. local
is the tool to do this:
program = do
-- Do stuff, including logging at the current level of verbosity
-- Now call programComponent with logging turned off
local (\_ -> Config 0) programComponent
-- And logging is turned back on if it was before the call to programComponent
programComponent :: Prog a
programComponent = ...
In this skeletal example, our program uses the user-specified logging level but
it calls programComponent
with a modified context where loggingLevel
is set
to 0. Note that this change really affects only programComponent
. Once the
call to programComponent
returns, the logging level is what it was before the
call. Hence the name local
. This function modifies the context locally.
The Reader
monad wrapped a function of type r -> a
, which represents a value
of type a
that depends on some context r
. The reader
function in the
MonadReader
class allows us turn such a function into a computation in any
reader monad m
. If m
is just the Reader
monad, then
reader f = ReaderT $ return . f
. We simply take the function and wrap it in
ReaderT
. For other instances of MonadReader
, the definition will likely look
different. For the RWST r w s m
monad, for example, we would have
reader f = RWST $ \r -> s -> return (f r, s, mempty)
.
The writer
and state
functions in the MonadWriter
and MonadState
classes
behave similarly. The Writer
monad wrapped a value of type (a, w)
. That was
our abstraction of a computation that produces a log of type w
along with its
return value. writer
lets us turn such a value into a computation in any monad
m
that is an instance of MonadWriter
. If m
is just the Writer
monad,
then writer f = WriterT $ return f
. For the RWST r w s m
monad, we have
writer (a, w) = RWST $ \_ -> s -> return (a, s, w)
.
The State
monad wapped a function of type s -> (a, s)
. That was our
abstraction of a computation that can read and modify some state of type s
along with producing a return value of type a
. state
lets us turn such a
function into a computation in any monad that is an instance of MonadState
. If
m
is just the State
monad, then state f = StateT $ return . f
. For the
RWST r w s m
monad, we have
state f = RWST $ \_ -> s -> let (a, s') = f s in return (a, s', mempty)
.
This leaves the listen
and pass
methods of the MonadWriter
class. First
listen
. When I said that the Writer
monad provides us with a write-only
log, I lied a little. That's how we should think about the log that this monad
provides; it's not some state that we can read and write at will. However, it
is possible to inspect the log while our computation runs. listen
is what
allows us to do this. If f
is a computation in our writer monad that produces
a result of type a
, then listen f
is a computation that returns a pair
consisting of f
's result and the value w
that was added to the log by f
.
In general, since w
is an arbitrary monoid, that's really just a value in this
monoid. This may be a bit abstract, so let's assume that w = [LogRecord]
, for
an appropriate LogRecord
type that we use to represent entries in our
program's log. In this case, what listen f
returns is the list of log records
produced by f
. It is important to note that this is not the entire log at
the time when listen f
returns. For example,
do
tell [logRecord1]
tell [logRecord2, logRecord3]
(result, logF) <- listen f
tell [logRecord4, logRecord5]
f :: Writer [LogRecord] a
f = do
...
tell [logRecordF1]
...
tell [logRecordF2, logRecordF3]
...
In this case, the log of our whole computation is
[logRecord1, logRecord2, logRecord3, logRecordF1, logRecordF2, logRecordF3]
immediately after listen f
returns, and the final log is
[logRecord1, logRecord2, logRecord3, logRecordF1, logRecordF2, logRecordF3, logRecord4, logRecord5]
.
The value assigned to logF
by listen f
is only the list of records produced
by f
: [logRecordF1, logRecordF2, logRecordF3]
.
pass
can be used to filter the log produced by a computation.1
pass f
takes a computation f
that does not only return a value x
of some
type a
but also a function flt
of type w -> w
. pass f
is a computation
that returns x
, but the log produced by pass f
is whatever we obtain by
applying flt
to the log produced by f
. This should once again become much
clearer using an example. Here, we assume that the log is just a list of
integers:
f :: Writer [Int] ((), [Int] -> [Int])
f = do
tell [1]
tell [10, 7, 8]
tell [9]
return ((), filter even)
g :: Writer ()
g = pass f
In this example, f
returns a pair consisting of ()
(void) and the function
filter even
that transforms a list of integers by throwing away all odd
numbers. The log produced by f
is [1, 10, 7, 8, 9]
. g = pass f
. Thus, g
returns the first component of the pair returned by f
, ()
. The log produced
by g
is whatever we obtain by applying the filter returned by f
to the log
produced by f
. Since the filter returned by f
is filter even
and the log
produced by f
is [1, 10, 7, 8, 9]
, g
produces the log
filter even [1, 10, 7, 8, 9] = [10, 8]
.
Now let's look at the last strangeness of these class definitions, the
function-like annotations m -> r
, m -> w
, and m -> s
in the class headers.
These are called functional dependencies. We discussed them briefly when
discussing type families. Let's look at the
MonadReader
type class. This type class takes two parameters r
and m
. An
instance MonadReader r m
says that m
is a reader monad that provides a
context of type r
. Without the functional dependency, there is nothing that
would prevent us from defining two such instances for the same monad:
instance MonadReader Int (Reader Int) where
...
instance MonadReader String (Reader Int) where
...
But this is obvious nonsense. If we have a Reader Int
monad, then the context
is of type Int
. ask
will return a value of type Int
, not String
. In
general, if we have a reader monad m
that provides some context, then this
context has some fixed type r
associated with this monad. The functional
dependency m -> r
says that it must be possible to figure out the context type
r
from the monad m
. In practical terms, this simply means that the compiler
will not allow us to define two MonadReader
instances for the same monad m
.
Multiple instances for different monads with the same context type r
are fine,
though. The dependency goes from m
to r
, that is, we must be able to
determine r
from m
, but there is no requirement that we know m
once we
know r
.
The other two annotations are analogous. Any state monad m
has a state of some
fixed type s
. We have the dependency m -> s
. Any writer monad m
has a log
of some fixed type w
. We have the dependency m -> w
.
-
While filtering the log is surely useful, the way this is done using
pass
appears strange to me, because the filter is produced by the same computation that produces the log, so it's not clear to me why we can't just produce the right log in the first place without the need to transform it afterwards.It seems more reasonable to me to have a function
f
that produces a log, and the caller off
may decide which off
's log messages it wants to keep as part off
's log. In fact, there exists exactly such a function:censor :: MonadWriter w m => (w -> w) -> m a -> m a
censor flt f
runsf
and then applies the filterflt
to transform the log produced byf
. ↩