Monads

The Mantra

Don’t Repeat Yourself

In this lecture we will see advanced ways to abstract code patterns











Outline

  1. Functors
  2. A Monad for Error Handling
  3. A Monad for Mutable State
  4. A Monad for Non-Determinism











Recall: HOF

Recall how we used higher-order functions to abstract code patters

Iterating Through Lists

data List a
  = []
  | (:) a (List a)




Rendering the Values of a List

-- >>> showList [1, 2, 3]
-- ["1", "2", "3"]

showList        :: [Int] -> [String]
showList []     =  []
showList (n:ns) =  show n : showList ns




Squaring the values of a list

-- >>> sqrList [1, 2, 3]
-- 1, 4, 9

sqrList        :: [Int] -> [Int]
sqrList []     =  []
sqrList (n:ns) =  n^2 : sqrList ns




Common Pattern: map over a list

Refactor iteration into mapList

mapList :: (a -> b) -> [a] -> [b]
mapList f []     = []
mapList f (x:xs) = f x : mapList f xs



Reuse mapList to implement showList and sqrList

showList xs = mapList (\n -> show n) xs

sqrList  xs = mapList (\n -> n ^ 2)  xs








Iterating Through Trees

data Tree a
  = Leaf
  | Node a (Tree a) (Tree a)




Rendering the Values of a Tree

-- >>> showTree (Node 2 (Node 1 Leaf Leaf) (Node 3 Leaf Leaf))
-- (Node "2" (Node "1" Leaf Leaf) (Node "3" Leaf Leaf))

showTree :: Tree Int -> Tree String
showTree Leaf         = Leaf
showTree (Node v l r) = Node (show v) (showTree l) (showTree r)






Squaring the values of a Tree

-- >>> sqrTree (Node 2 (Node 1 Leaf Leaf) (Node 3 Leaf Leaf))
-- (Node 4 (Node 1 Leaf Leaf) (Node 9 Leaf Leaf))

sqrTree :: Tree Int -> Tree Int
sqrTree Leaf         = Leaf
sqrTree (Node v l r) = Node (v^2) (sqrTree l) (sqrTree r)




Common Pattern: map over a tree

Refactor iteration into mapTree

mapTree :: (a -> b) -> Tree a -> Tree b
mapTree f Leaf       = Leaf
mapTree f (Node x l r) = Node (f x) (mapTree f l) (mapTree f r)











Abstracting across Datatypes

Wait, this looks familiar…

type List a = [a]
mapList :: (a -> b) -> List a -> List b    -- List
mapTree :: (a -> b) -> Tree a -> Tree b    -- Tree


Can we provide a generic map function that works for List, Tree, and other datatypes?











A Class for Mapping

Not all datatypes support mapping over, only some of them do.

So let’s make a typeclass for it!

class Functor t where
  fmap :: ???











QUIZ

What type should we give to fmap?

class Functor t where
  fmap :: ???

(A) (a -> b) -> t -> t

(B) (a -> b) -> [a] -> [b]

(C) (a -> b) -> t a -> t b

(D) (a -> b) -> Tree a -> Tree b

(E) None of the above













class Functor t where
  fmap :: (a -> b) -> t a -> t b

Unlike other typeclasses we have seen before, here t:

  • does not stand for a type (of kind *)
  • but for a type constructor (of kind `* -> *`)
  • it is called a higher-kinded type variable







Reuse Iteration Across Types

instance Functor [] where
  fmap = mapList

instance Functor Tree where
  fmap = mapTree

And now we can do

-- >>> fmap show [1,2,3]
-- ["1", "2", "3"]


-- >>> fmap (^2) (Node 2 (Node 1 Leaf Leaf) (Node 3 Leaf Leaf))
-- (Node 4 (Node 1 Leaf Leaf) (Node 9 Leaf Leaf))











EXERCISE: the Maybe Functor

Write a Functor instance for Maybe:

data Maybe a = Nothing | Just a

instance Functor Maybe where
  fmap = ???

When you’re done you should see

-- >>> fmap (^ 2) (Just 3)
Just 9

-- >>> fmap (^ 2) Nothing
Nothing











Outline

  1. Functors [done]
  2. A Monad for Error Handling
  3. A Monad for Mutable State
  4. A Monad for Non-Determinism











Next: A Class for Sequencing

I want to write a calculator app

Let’s start with simple arithmetic expressions:

data Expr
  = Num    Int
  | Plus   Expr Expr
  | Div    Expr Expr
  deriving (Show)

Let us write a function:

eval :: Expr -> Int
eval = ???

-- >>> eval (Plus (Num 2) (Num 5))
-- 7

-- >>> eval (Div (Num 6) (Num 2))
-- 3





But what is the result of

-- >>> eval (Div (Num 6) (Num 0))
-- *** Exception: divide by zero



My interpreter crashes!

  • What if I’m implementing GHCi?
  • I don’t want GHCi to crash every time you enter div 5 0
  • I want it to process the error and move on with its life

How can we achieve this behavior?








Error Handling: Take One

Let’s introduce a new type for evaluation results:

data Result  a
  = Error String
  | Value a

Our eval will now return Result Int instead of Int

  • If a sub-expression had a divide by zero, return Error "..."
  • If all sub-expressions were safe, then return the actual Value v








EXERCISE: Interpreter with Result

data Result  a = Error String | Value a

eval :: Expr -> Result Int
eval (Num n)      = ???
eval (Plus e1 e2) = ???
eval (Div e1 e2)  = ???


HINT: To pattern-match on a Result, use a case expression:

case eval something of
  Error msg -> ...
  Value v   -> ...











eval :: Expr -> Result Int
eval (Num n)      = Value n
eval (Plus e1 e2) = 
  case eval e1 of
    Error err1 -> Error err1
    Value v1   -> case eval e2 of
                    Error err2 -> Error err2
                    Value v1   -> Value (v1 + v2)
eval (Div e1 e2)  = 
  case eval e1 of
    Error err1 -> Error err1
    Value v1   -> case eval e2 of
                    Error err2 -> Error err2
                    Value v2   -> if v2 == 0 
                                    then Error ("DBZ: " ++ show e2)
                                    else Value (v1 `div` v2)



The good news: interpreter doesn’t crash, just returns Error msg:

λ> eval (Div (Num 6) (Num 2))
Value 3
λ> eval (Div (Num 6) (Num 0))
Error "DBZ: Num 0"
λ> eval (Div (Num 6) (Plus (Num 2) (Num (-2))))
Error "DBZ: Plus (Num 2) (Num (-2))"



The bad news: the code is super duper gross











Lets spot a Pattern

The code is gross because we have these cascading blocks

case eval e1 of
  Error err1 -> Error err1
  Value v1   -> case eval e2 of
                  Error err2 -> Error err2
                  Value v2   -> Value (v1 + v2)



But these blocks have a common pattern:

  • First do eval e and get result res
  • If res is an Error, just return that error
  • If res is a Value v then do further processing on v



case res of
  Error err -> Error err
  Value v   -> process v -- do more stuff with v



Bottling a Magic Pattern

Lets bottle that common structure in a function >>= (pronounced bind):

(>>=) :: Result a -> (a -> Result b) -> Result b
(Error err) >>= _       = Error err
(Value v)   >>= process = process v



Notice the >>= takes two inputs:

  • Result a: result of the first evaluation
  • a -> Result b: in case the first evaluation produced a value, what to do next with that value











QUIZ: Bind 1

With >>= defined as before:

(>>=) :: Result a -> (a -> Result b) -> Result b
(Error msg) >>= _       = Error msg
(Value v)   >>= process = process v

What does the following evaluate to?

λ> eval (Num 5)   >>=   \v -> Value (v + 1)

(A) Type Error

(B) 5

(C) Value 5

(D) Value 6

(E) Error msg


Answer: D











QUIZ: Bind 2

With >>= defined as before:

(>>=) :: Result a -> (a -> Result b) -> Result b
(Error msg) >>= _       = Error msg
(Value v)   >>= process = process v

What does the following evaluate to?

λ> Error "nope"   >>=   \v -> Value (v + 1)

(A) Type Error

(B) 5

(C) Value 5

(D) Value 6

(E) Error "nope"


Answer: E









A Cleaned up Evaluator

The magic bottle lets us clean up our eval:

eval :: Expr -> Result Int
eval (Num n)      = Value n
eval (Plus e1 e2) = eval e1 >>= \v1 ->
                    eval e2 >>= \v2 ->
                    Value (v1 + v2)
eval (Div e1 e2)  = eval e1 >>= \v1 ->
                    eval e2 >>= \v2 ->
                    if v2 == 0
                      then Error ("DBZ: " ++ show e2)
                      else Value (v1 `div` v2)

The gross pattern matching is all hidden inside >>=!



NOTE: It is crucial that you understand what the code above is doing, and why it is actually just a “shorter” version of the (gross) nested-case-of eval.









A Class for bind

Like fmap or show or ==, the >>= operator turns out to be useful across many types (not just Result)



Let’s create a typeclass for it!

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



return tells you how to wrap an a value in the monad

  • Useful for writing code that works across multiple monads









Monad instance for Result

Let’s make Result an instance of Monad!

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

instance Monad Result where
  (>>=) :: Result a -> (a -> Result b) -> Result b
  (Error msg) >>= _       = Error msg
  (Value v)   >>= process = process v

  return :: a -> Result a
  return v = ??? -- How do we make a `Result a` from an `a`?













instance Monad Result where
  (>>=) :: Result a -> (a -> Result b) -> Result b
  (Error msg) >>= _       = Error msg
  (Value v)   >>= process = process v

  return :: a -> Result a
  return v = Value v









Syntactic Sugar

In fact >>= is so useful there is special syntax for it!

  • It’s called the do notation



Instead of writing

e1 >>= \v1 ->
e2 >>= \v2 ->
e3 >>= \v3 ->
e

you can write

do v1 <- e1
   v2 <- e2
   v3 <- e3
   e





Thus, we can further simplify our eval to:

eval :: Expr -> Result Int
eval (Num n)      = return n
eval (Plus e1 e2) = do v1 <- eval e1
                       v2 <- eval e2
                       return (v1 + v2)
eval (Div e1 e2)  = do v1 <- eval e1
                       v2 <- eval e2
                       if v2 == 0
                         then Error ("DBZ: " ++ show e2)
                         else return (v1 `div` v2)









Aside: IO is a Monad!

  • Recall that we used the do notation for Recipe / IO
  • Now you know that do is just a special syntax for >>=!
  • And IO is just one instance of Monad!









The Either Monad

Error handling is a very common task!

Instead of defining your own type Result, you can use Either from the Haskell standard library:

data Either a b = 
    Left  a  -- something has gone wrong
  | Right b  -- everything has gone RIGHT

Either is already an instance of Monad, so no need to define your own >>=!



Now we can simply define

type Result a = Either String a

and the eval above will just work out of the box!









Outline

  1. Functors [done]
  2. A Monad for Error Handling [done]
  3. A Monad for Mutable State
  4. A Monad for Non-Determinism









Expressions with a Counter

Consider implementing expressions with a counter:

data Expr
  = Num    Int
  | Plus   Expr Expr
  | Next   -- counter value
  deriving (Show)

Behavior we want:

  • eval is given the initial counter value
  • every time we evaluate Next (within the call to eval), the value of the counter increases:
--        0
λ> eval 0 Next
0

--              0    1
λ> eval 0 (Plus Next Next)
1

λ> eval 0 (Plus Next (Plus Next Next))
???









--              0          1    2
λ> eval 0 (Plus Next (Plus Next Next))
3







How should we implement eval?

eval (Num n)      cnt = ???
eval Next         cnt = ???
eval (Plus e1 e2) cnt = ???











QUIZ: State: Take 1

If we implement eval like this:

eval (Num n)      cnt = n
eval Next         cnt = cnt
eval (Plus e1 e2) cnt = eval e1 cnt + eval e2 cnt

What would be the result of the following?

λ> eval (Plus Next Next) 0

(A) Type error

(B) 0

(C) 1

(D) 2


Answer: B











It’s going to be 0 because we never increment the counter!

  • We need to increment it every time we do eval Next
  • So eval needs to return the new counter











Evaluating Expressions with Counter

type Cnt = Int
  
eval :: Expr -> Cnt -> (Cnt, Int)
eval (Num n)      cnt = (cnt, n)
eval Next         cnt = (cnt + 1, cnt)
eval (Plus e1 e2) cnt = let (cnt1, v1) = eval e1 cnt
                        in 
                          let (cnt2, v2) = eval e2 cnt1
                          in
                            (cnt2, v1 + v2)
                       
topEval :: Expr -> Int
topEval e = snd (eval e 0)



The good news: we get the right result:

λ> topEval (Plus Next Next)
1

λ> topEval (Plus Next (Plus Next Next))
3



The bad news: the code is super duper gross.

The Plus case has to “thread” the counter through the recursive calls:

let (cnt1, v1) = eval e1 cnt
  in 
    let (cnt2, v2) = eval e2 cnt1
    in
      (cnt2, v1 + v2)
  1. Easy to make a mistake, e.g. pass cnt instead of cnt1 into the second eval!
  2. The logic of addition is obscured by all the counter-passing

So unfair, since Plus doesn’t even care about the counter!





Is it too much to ask that eval looks like this?

eval (Num n)      = return n
eval (Plus e1 e2) = do v1 <- eval e1
                       v2 <- eval e2
                       return (v1 + v2)
...                       
  • Cases that don’t care about the counter (Num, Plus), don’t even have to mention it!
  • The counter is somehow threaded through automatically behind the scenes
  • Looks just like in the error handing evaluator











Lets spot a Pattern

let (cnt1, v1) = eval e1 cnt
  in 
    let (cnt2, v2) = eval e2 cnt1
    in
      (cnt2, v1 + v2)

These blocks have a common pattern:

  • Perform first step (eval e) using initial counter cnt
  • Get a result (cnt', v)
  • Then do further processing on v using the new counter cnt'
let (cnt', v) = step cnt
in process v cnt' -- do things with v and cnt'



Can we bottle this common pattern as a >>=?

(>>=) step process cnt = let (cnt', v) = step cnt
                         in process v cnt'



But what is the type of this >>=?










(>>=) :: (Cnt -> (Cnt, a)) 
         -> (a -> Cnt -> (Cnt, b)) 
         -> Cnt 
         -> (Cnt, b)
(>>=) step process cnt = let (cnt', v) = step cnt
                         in process v cnt'

Wait, but this type signature looks nothing like the Monad’s bind!

(>>=)  :: m a -> (a -> m b) -> m b



… or does it???











QUIZ: Type of bind for Counting

What should I replace m t with to make the general type of monadic bind:

(>>=)  :: m a -> (a -> m b) -> m b

look like the type of bind we just defined:

(>>=) :: (Cnt -> (Cnt, a)) 
         -> (a -> Cnt -> (Cnt, b)) 
         -> Cnt 
         -> (Cnt, b)

(A) It’s impossible

(B) m t = Result t

(C) m t = (Cnt, t)

(D) m t = Cnt -> (Cnt , t)

(E) m t = t -> (Cnt , t)











type Counting a = Cnt -> (Cnt, a)

(>>=) :: Counting a 
         -> (a -> Counting b) 
         -> Counting b
(>>=) step process = \cnt -> let (cnt', v) = step cnt
                             in process v cnt'

Mind blown.











QUIZ: Return for Counting

How should we define return for Counting?

type Counting a = Cnt -> (Cnt, a)

-- | Represent value x as a counting computation,
-- don't actually touch the counter
return :: a -> Counting a
return x = ???

(A) x

(B) (0, x)

(C) \c -> (0, x)

(D) \c -> (c, x)

(E) \c -> (c + 1, x)


Answer: D









Cleaned-up evaluator

eval :: Expr -> Counting Int
eval (Num n)      = return n
eval (Plus e1 e2) = eval e1 >>= \v1 ->
                    eval e2 >>= \v2 ->
                    return (v1 + v2)
eval Next         = \cnt -> (cnt + 1, cnt)

Hooray! We rid the poor Num and Plus from the pesky counters!



The Next case has to deal with counters

  • but can we somehow hide the representation of Counting a?
  • and make it look more like we just have mutable state that we can get and put?
  • i.e. write:
eval Next         = get         >>= \c ->
                    put (c + 1) >>= \_ ->
                    return c









EXERCISE: getting and putting

Define the functions:

-- | Computation whose return value is the current counter value
get :: Counting Cnt
get = ???

-- | Computation that updates the counter value to `newCnt`
put :: Cnt -> Counting ()
put newCnt = ???

so that we can write:

eval Next         = get         >>= \c ->
                    put (c + 1) >>= \_ ->
                    return c









-- | Computation whose return value is the current counter value
get :: Counting Cnt
get = \cnt -> (cnt, cnt)

-- | Computation that updates the counter value to `newCnt`
put :: Cnt -> Counting ()
put newCnt = \_ -> (newCnt, ())









Monad instance for Counting

Let’s make Counting an instance of Monad!

  • To do that, we need to make it a new datatype
data Counting a = C (Cnt -> (Cnt, a))

instance Monad Counting where
  (>>=) :: Counting a -> (a -> Counting b) -> Counting b
  (>>=) (C step) process = C final
    where
      final cnt = let 
                    (cnt', v) = step cnt
                    C nextStep = process v      
                  in nextStep cnt' 

  return :: a -> Result a
  return v = C (\cnt -> (cnt, v))

We also need to update get and put slightly:

-- | Computation whose return value is the current counter value
get :: Counting Cnt
get = C (\cnt -> (cnt, cnt))

-- | Computation that updates the counter value to `newCnt`
put :: Cnt -> Counting ()
put newCnt = C (\_ -> (newCnt, ()))











Cleaned-up Evaluator

Now we can use the do notation!

eval :: Expr -> Counting Int
eval (Num n)      = return n
eval (Plus e1 e2) = do v1 <- eval e1
                       v2 <- eval e2
                       return (v1 + v2)
eval Next         = do
                      cnt <- get
                      _ <- put (cnt + 1)
                      return (cnt)                      











The State Monad

Threading state is a very common task!

Instead of defining your own type Counting a, you can use State s a from the Haskell standard library:

data State s a = State (s -> (s, a))

State is already an instance of Monad, so no need to define your own >>=!



Now we can simply define

type Counting a = State Cnt a

and the eval above will just work out of the box!











Outline

  1. Functors [done]
  2. A Monad for Error Handling [done]
  3. A Monad for Mutable State [done]
  4. A Monad for Non-Determinism











Recall: Computations that may fail

-- | Result sans the error message
data Result a = Value a | Error

instance Monad Result where
  Error      >>= _       = Error
  (Value v)  >>= process = process v

  return v = Value v



A computation of type Result a returns zero or one a

Can we generalize this to computations that return zero or more as?









Replacing Failure by a List of Successes

Instead of Result a let’s return [a]!

  • Instead of Error, return the empty list []
  • Instead of Value v, return the singleton list [v]

… can we do something fun with many elements?










QUIZ

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

instance Monad [] where 
  return = listReturn
  (>>=)  = listBind

What must the type of listReturn be ?

A. [a]

B. a -> a

C. a -> [a]

D. [a] -> a

E. [a] -> [a]










Return for Lists

Let’s implement return for lists?

listReturn :: a -> [a]
listReturn x = ???

What’s the only sensible implementation?












QUIZ

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

instance Monad [] where 
  return = listReturn
  (>>=)  = listBind

What must the type of listBind be?

A. [a] -> [b] -> [b]

B. [a] -> (a -> b) -> [b]

C. [a] -> (a -> [b]) -> b

D. [a] -> (a -> [b]) -> [b]

E. [a] -> [b]












EXERCISE: Bind for Lists

What is the most sensible implementation of listBind?

listBind :: [a] -> (a -> [b]) -> [b] 
listBind = ???



HINT: What does “sensible” mean?

Recall how we discussed that the implementation of map is the only sensible one for its type:

map :: (a -> b) -> [a] -> [b]
map f []     = []
map f (x:xs) = f x : map f xs

You could of course implement:

  • map f xs = []
  • or map f (x:xs) = [f x]

but this is silly because it doesn’t use all the elements of the input list!












Bind for Lists

listBind :: [a] -> (a -> [b]) -> [b] 
listBind []     _ = []
listBind (x:xs) f = f x ++ listBind xs f

or, without recursion:

listBind xs f = concat (map f xs)

there’s already a library function for this!

listBind xs f = concatMap f xs






For example:

f = \x -> [x, x+1]


[]      >>= f                      ==> []

[1]     >>= f ==> f 1              ==> [1,2]

[1,2]   >>= f ==> f 1 ++ f 2       ==> [1,2,2,3]

[1,2,3] >>= f ==> f 1 ++ f 2 ++ f3 ==> [1,2,2,3,3,4]












QUIZ

What does the following program evaluate to?

quiz = do x <- ["cat", "dog"]
          y <- [0, 1]
          return (x, y)

A. []

B. [("cat", 0)]

C. ["cat", "dog", 0, 1]

D. ["cat", 0, "dog", 1]

E. [("cat", 0), ("cat", 1), ("dog", 0), ("dog", 1)]









Does this behavior ring a bell?









Whoa, behaves like a list comprehension!

quiz = do x <- ["cat", "dog"]
          y <- [0, 1]
          return (x, y)

is equivalent to:

quiz = [ (x, y) | x <- ["cat", "dog"], y <- [0, 1] ]

List comprehensions are just a syntactic sugar for the List Monad!



For those who are not comfortable with list comprehensions, think nested for-loops






Lets work it out.

do {x <- ["cat", "dog"]; y <- [0, 1]; return (x, y)}

== ["cat", "dog"] >>= (\x -> [0, 1] >>= (\y -> return (x, y)))

Now lets break up the evaluation

[0, 1] >>= (\y -> [(x, y)])

==> [(x, 0)] ++ [(x, 1)]

==> [(x, 0), (x, 1)] 

So

["cat", "dog"] >>= (\x -> [(x, 0), (x, 1)])

==> [("cat", 0), ("cat", 1)] ++ [("dog", 0), ("dog", 1)] 

==> [("cat", 0), ("cat", 1), ("dog", 0), ("dog", 1)] 











QUIZ

What does the following evaluate to?

quiz = do x <- ["cat", "dog"]
          y <- [0, 1]
          []

A. []

B. [[]]

C. [()]

D. [("cat", 0)]

E. [("cat", 0), ("cat", 1), ("dog", 0), ("dog", 1)]










EXERCISE: Co-primes

Recall finding co-primes using list comprehensions:

-- first n pairs of co-primes: 
coPrimes n = take n [(i,j) | i <- [2..],
                             j <- [2..i],
                             gcd i j == 1]

Rewrite this using the List Monad

  • assume that the gcd function is already defined
coPrimes n = take n allCoPrimes
  where
    allCoPrimes = ???












Beyond List Comprehensions

List comprehensions / nested for-loops = cartesian product of a fixed number of lists

For example:

-- cartesian product of 2 lists
[ (x, y) | x <- ["cat", "dog"], y <- [0, 1] ]
>>> [("cat", 0), ("cat", 1), ("dog", 0), ("dog", 1)]

What if we want to do the same thing for an arbitrary number of lists?

  • this gets REALLY HAIRY in imperative languages
  • but ridiculously easy in Haskell












Example: All Bit Strings of Length n

Let’s implement a function:

bits :: Int -> [String]

Such that

>>> bits 0 
[""]
>>> bits 1
["0", "1"]
>>> bits 2 
["00", "01", "10", "11"]

>>> bits 3 
["000", "001", "010", "011", "100", "101", "110", "111"]












bits :: Int -> [String]
bits 0 = return ""
bits n = do
            bit <- ['0', '1']
            rest <- bits (n - 1)
            return (bit:rest)












Useful Library Functions

We can often eliminate recursion from monadic computations using library functions:

-- From Control.Monad:

-- | Map a monadic computation over a list, get list of results:
mapM       :: Monad m => (a -> m b) -> [a] -> m [b]
-- | Repeat the same monadic computation n times, get list of results:
replicateM :: Monad m => Int -> m a -> m [a]

-- For example:
bits n = mapM (\_ -> ['0', '1']) [1..n]

-- or:
bits n = replicateM n ['0', '1']












Summary

Three monads and their meaning of sequencing:

Result / Either monad for error handling:

  • if step 1 fails, then stop
  • if step 1 succeeds, then do step 2

State monad for mutable state:

- do step 1 to get a new state
- do step 2 in that new state

List monad for non-determinism / enumeration:

- do step 1 to get a list of intermediate results
- for each intermediate result, do step 2












Monads are Amazing

This code stays the same:

eval :: Expr -> Interpreter Int
eval (Num n)      = return n
eval (Plus e1 e2) = do v1 <- eval e1
                       v2 <- eval e2
                       return (v1 + v2)
...                       

We can change the type Interpreter to implement different effects:

  • type Interpreter a = Either String a if we want to handle errors
  • type Interpreter a = State Int a if we want to have a counter
  • type Interpreter a = [a] if we want to return multiple results

Later we will see how to combine effects with monad transformers!



Monads let us decouple two things:

  1. Application logic: the sequence of actions (implemented in eval)
  2. Effects: how actions are sequenced (implemented in >>=)








Monads are Influential

Monads have had a revolutionary influence in PL, well beyond Haskell, some recent examples

  • Error handling in go e.g. 1
    and 2

  • Asynchrony in JavaScript e.g. 1 and 2

  • Big data pipelines e.g. LinQ and TensorFlow








Thats all, folks!