Lecture 14: Concrete Monads: Writer, Reader

The midterm exam will be Monday, November 4th, in class.

Background

We often think of monads as a mechanism for adding “effects” to our computations. E.g., if we want to add non-determinism as an effect, we can do this by considering lists of results. Working within the list monad enables us to use binding as a means of representing non-deterministic choice, and so hides the complexity by allowing the programmer to focus on the non-deterministic choices made, and hides the mechanism for organizing those choices, and assembling the results.

A complication comes from when we try to layer effects, e.g., we want to combine non-deterministic computation with IO. The problem here is that, unlike functors and applicatives, monads don't compose, i.e., there is no natural way to define an instance

instance (Monad m, Monad n) => Monad (Compose m n)

A solution comes from the notion of monad transformers, a sophisticated approach that enables us to build layered effects. The monad transformer library (mtl) defines a number of monad transformers. As the kind of a monad is * -> *, it is unsurprising that the kind of a monad transformer is (* -> *) -> * -> *. For example, if we have some sort of effect “foo,” we'll have a monad transformer FooT, such that whenever m is a monad, then FooT m will also be a monad, but one that layers the “foo” effect onto the effects of m.

Associated with each of the FooT transformers, is the class Foo = FooT Identity, which is a monad that has only the “foo” effect. Doing things this way saves the library implementor some work, but it does incur a cost on the ordinary programmer. If you make a type error in the context of a Foo monad, you're liking to see errors referring to FooT Identity, which can be disorienting, especially if you encounter them before you've seen monad transformers, or understand how the Foo type constructor is implemented “under the hood.”

There's also a type class MonadFoo which contains all of the functions and constants that we associate with the “foo” effect, and naturally there's a MonadFoo instance of FooT m. But the mad genius of the monad transformer library is that for each of the other monad transformers (e.g., BarT), there's a derived instance

instance MonadFoo m => MonadFoo (BarT m)

This has the consequence that when we add a “foo” effect, our work is not undone by further transformations. This matters! But this makes for a complicated library (briefly, the number of derived instances definitions has to grow quadratically with the number of base transformers). Again, this is a case where details of the implementation can unexpected “leak out,” as the functions we associate with Foo aren't to be found in the definition of Foo, but rather in the related MonadFoo type class.

The mechanics of making the monad transformer library work are not for the faint-of-heart, but fortunately, we don't need to learn them all at once. An important first step is to understand the kind of “effect” that each transformer adds. We can study these effects in isolation by considering Foo = FooT Identity for each of the monad transformers, and so learn the basic building blocks of the mtl.

A Motivating Example

The core of many programs are evaluators of some sort. If we want effects in our evaluation process, it's common to have evaluation monads. To make things easy we'll construct an Expr n type, which is based on Num. We start with

data UnaryOp = Abs | Signum deriving (Show) data BinOp = Add | Subtract | Multiply deriving (Show) data Expr n = Value n | ApplyBinary BinOp (Expr n) (Expr n) | ApplyUnary UnaryOp (Expr n) deriving (Show)

Next, we'll make Expr n an instance of Num:

instance Num n => Num (Expr n) where (+) = ApplyBinary Add (-) = ApplyBinary Subtract (*) = ApplyBinary Multiply abs = ApplyUnary Abs signum = ApplyUnary Signum fromInteger = Value . fromInteger

This is a bit surprising. We're not doing computational work here, but instead are using the Num instance as a vehicle for translating from ordinary notation for simple expressions to our particular data type. In effect, we're deferring the actual evaluation of these operations until later. A simple test shows what we've done.

> 1 + 2 * 3 :: Expr Int ApplyBinary Add (Value 1) (ApplyBinary Multiply (Value 2) (Value 3))

We're going to use a monad for evaluation, but because we have no effects, we'll keep the monad as simple as possible:

type Eval = Identity

Our goal is to write a function eval :: (Num n) => Expr n -> Eval n. We'll abstract out the patterns of applying binary and unary operators via corresponding helper functions:

-- | Evaluate an expression in the Eval monad. eval :: (Num n,Show n) => Expr n -> Eval n eval (Value n) = pure n eval (ApplyBinary Add e1 e2) = applyBinary (+) e1 e2 eval (ApplyBinary Subtract e1 e2) = applyBinary (-) e1 e2 eval (ApplyBinary Multiply e1 e2) = applyBinary (*) e1 e2 eval (ApplyUnary Abs expr) = applyUnary abs expr eval (ApplyUnary Signum expr) = applyUnary signum expr -- | Evaluate the result of applying a binary operator to a pair of expressions, in the -- Eval monad. applyBinary :: (Num n,Show n) => (n -> n -> n) -> Expr n -> Expr n -> Eval n applyBinary op e1 e2 = do v1 <- eval e1 v2 <- eval e2 let result = v1 `op` v2 pure result -- | Evaluate the result of applying a unary operator to an expression, in the -- Eval monad. applyUnary :: (Num n,Show n) => (n -> n) -> Expr n -> Eval n applyUnary op expr = do v1 <- eval expr let result = op v1 pure result

These helper functions could be η-reduced, but let's leave them as is for now.

With this machinery, we're set up to do simple evaluation:

> runIdentity . eval $ 1 + 2 * 3 7

Writer

Let's consider a simple effect we might want to add to our evaluator. We'd like to add a logging capability, so that we construct a record of computational work as it's being done.

The Writer w a represents a type where w is the type of the values we're writing, and a is the type of the value we're computing.

For the purposes of this lecture, we'll write our own Writer module, intended as a work-alike replacement for Control.Monad.Writer for dealing with simple Writer types. If we do our work well (and of course we will), we'll be able to build our example program using our Writer module, and then simply replace the import of Writer with Control.Monad.Writer, and have everything work, even though the implementation of Writer in Control.Monad.Writer actually goes via WriterT. Values of Writer w a have to encode both a message of type w, and a value of type a.

newtype Writer w a = Writer { runWriter :: (a,w) }

The “twist” in the order of w and a is a bit annoying, and will require constant attention as we code.

We start by providing a Functor instance, and it's easy:

instance Functor (Writer w) where fmap f (Writer (a,w)) = Writer (f a, w)

The Applicative instance hints at things to come. To implement <*>, we'll take two values of this type, containing both values and messages, and have to combine them. Combining the values is straightforward: one of the values is a function of type a -> b, and the other is a value of type a. We simply apply the function to the value, and we're set. But what about the messages? We need a way to combine messages. Moreover, to implement pure, we need a way to conjure up a message from thin air. To make both possible, we'll add the constraint that w be a Monoid. Thus

instance Monoid w => Applicative (Writer w) where pure a = Writer (a,mempty) (Writer (fa,fw)) <*> (Writer (xa,xw)) = Writer (fa xa, fw <> xw)

*Exercise 14.1 Write a suitable Monad instance for Writer w.

Associated with this monad are a number of useful functions. We'll use two in our example, the rest can be discovered by reading the code and documentation.

-- | Construct a writer action with a given message. tell :: w -> Writer w () tell w = Writer ((),w) -- | An fmap-like function that acts on the message component of a writer action. censor :: Monoid w => (w -> w) -> Writer w a -> Writer w a censor f (Writer (a,w)) = Writer (a,f w)

Our completed Writer module (modulo the definition of (>>=)) is Writer.hs.

Example: WriterEval

We want to add logging to our evaluator. This requires a few changes, but perhaps less than you'd think. First, we have to define Eval so that it takes into account writer effects.

type Eval = Writer [(String,String)]

The type of our message is a list of pairs. Lists are nice monoids, and the idea is that each of the pairs will correspond to a line of output. Each pair encodes an operation that was applied, and a brief description. We've done this for a reason...

It is often the case that we build a little private language on top of our effects, and we find it useful to have the following:

-- | Log a message that an operation was performed. note :: String -> [String] -> Eval () note op ws = tell [(op,unwords ws)]

The note function uses tell to append a pair (with our intended interpretation) onto the message that's being built.

Our eval function now has to be reoriented a bit to account for logging:

eval :: (Num n,Show n) => Expr n -> Eval n eval (Value n) = pure n eval (ApplyBinary Add e1 e2) = applyBinary "+" (+) e1 e2 ... eval (ApplyUnary Abs expr) = applyUnary "abs" abs expr ...

The difference is that we have to print out values in our log, and so our underlying numeric type needs to be an instance of Show, and our “apply” functions are going to need a printable name for the function that's being applied. Note that would could have handled this in other ways, but this is simple.

applyBinary :: (Num n,Show n) => String -> (n -> n -> n) -> Expr n -> Expr n -> Eval n applyBinary name op e1 e2 = do v1 <- eval e1 v2 <- eval e2 let result = v1 `op` v2 note name [show v1,name,show v2,"=",show result] pure result

Our implementation of applyBinary has to handle that extra string argument, produce an appropriate message, which we do by adding the note line. The changes to applyUnary are similar.

We're now set up to use this machinery, via the showWork function:

-- | Perform an evaluation in our Eval monad, formatting our message log, -- and sending it to standard output. showWork :: (Num n,Show n) => Expr n -> IO () showWork expr = do let (result,output) = runWriter . eval $ expr putStr . unlines . map snd $ output putStrLn $ "The final answer is " ++ show result ++ "."

Now,

> showWork $ (2+3) * (4+5) 2 + 3 = 5 4 + 5 = 9 5 * 9 = 45 The final answer is 45.

If only we'd had this in third grade. Of course, we don't spend our entire life in third grade, but must in due course move along to fourth. As you know, “showing your work” never meant to show the trivial steps, just the hard/interesting ones. By fourth grade, it's assumed you can do addition and subtraction, but you still have to show your multiplication steps. We accomplish this with a simple change to the showWork function, slipping in a function that filters the message list, retaining only the hard steps:

-- | Perform an evaluation in our Eval monad, filtering our message log down to the -- hard steps, formatting it, and sending it to standard output. showHardWork :: (Num n,Show n) => Expr n -> IO () showHardWork expr = do let (result,output) = runWriter . censor (filter isHard) . eval $ expr putStr . unlines . map snd $ output putStrLn $ "The final answer is " ++ show result ++ "." where isHard (op,_) = op == "*"

Now,

> showHardWork $ 10 * 12 + 11 * 11 10 * 12 = 120 11 * 11 = 121 The final answer is 241.

We're making good progress, and are now ready for fifth grade. Our example code is WriterEval.hs

Reader

Let's consider a different kind of effect. We'd like to beef up our evaluation system a little bit, allowing ourselves to save and re-use computed values. To that end, we need to introduce variables and binding expressions to our Expr type:

data Expr n = ... | Variable String | Let [(String,Expr n)] (Expr n)

Evaluation now needs to take place in a context that can maintain a list of bindings. For this, we introduce the Reader type. The idea is that the type Reader e a will wrap a function of type e -> a. We use e, because we're thinking of this as the environment of the computation. As before, we'll build a work-alike module Reader that implements the Reader type directly, rather than via ReaderT.

newtype Reader e a = Reader { runReader :: e -> a }

We can recognize this as a wrapped version of (->) e, and simply lift the Functor, Applicative, and Monad instances from there. As this involves nothing new (although some of the type swizzling is usually annoying), we'll elide it, but the definitions are in the source file.

Exercise 14.2 Write your own Functor, Applicative, and Monad for Reader e, and compare them with the definitions in Reader.hs.

The standard Reader functions are

-- | Retrieve the environment. ask :: Reader e e ask = Reader id -- | Run an action in a modified environment. local :: (e -> e) -> Reader e a -> Reader e a local f (Reader g) = Reader $ g . f -- | Retrieve a function applied to the current environment. asks :: (e -> a) -> Reader e a asks f = Reader f

These seem quite simple, but they are powerful building blocks.

Example: ReaderEval

Our goal now is to implement a more powerful evaluator, one that allows the use of variables and bindings. For now, our goal will be to evaluate

testExpr :: Expr Int testExpr = let x = Variable "x" y = Variable "y" in Let [ ("y",10) ] $ Let [("x", y + y)] (x * x - y * y)

First, we define our evaluation monad

type Eval n = Reader [(String,n)] n

Note that the ‘environment’ in this case is a simple association list.

To keep our code simple, we'll use a crashing lookup function,

-- | Look up a value in an association list, crashing if there is no such value. lookup' :: String -> [(String,n)] -> n lookup' var env = case lookup var env of Just val -> val Nothing -> error $ "Unknown variable " ++ var

This isn't elegant, but trying to combine error handling via Maybe with the implicit environment of Reader puts us into the position of trying to layer effects, and we're not quite ready for that.

With this, we can handle variables easily

eval (Variable v) = asks (lookup' v)

All this does is to encapsulate the action of looking up the name of a variable in the (implicit) current environment, which is exactly what we need.

Unsurprisingly, most of the work is in evaluating Let expressions. To do this we first extract the keys from the binding list, then we evaluate the expressions to be bound from the binding list, then we create an association list of the keys and values resulting from this evaluation, then we modify the existing environment to include the newly bound variables, and finally we evaluate the body of the Let in the resulting environment. This sounds like a lot, but it's not so bad:

eval (Let bindings expr) = do let ks = map fst bindings vs <- mapM (eval . snd) bindings local (zip ks vs ++) $ eval expr

Oddly enough, this is all we have to do. Add a couple of new lines to our Expr definition, set our evaluation monad to be the appropriate Reader, add a couple cases to our eval function, and we're pretty much set. Oh, and evaluating testExpr? All we have to do is use eval to create a value in the evaluation monad, use runReader to extract the underlying function, and then apply it to an empty environment.

> runReader (eval testExpr) [] 300

Profit!

ReaderEval.hs