Lecture 11 — 2018-02-22

Monads

This lecture is written in literate Haskell; you can download the raw source.

import Control.Applicative
import Data.IORef
import System.IO

After some logistics, we tried to write a parser for a language like the following:

n, m are natural numbers

n : m_1 m_2 ... m_n

GOOD EXAMPLES:

0 :
1 : 2
2 : 20 27

BAD EXAMPLES:

0 : 73 5 3
2 : 1
hello

We want our parser to return the list of ints that comes after the count. We can write the first part pretty easily:

count :: Parser Int
count = num <* char ':'

And, given the count, we can write the rest with some helper functions:

list :: Int -> Parser [Int]
list n = sequenceA (replicate n num) <* eof

But how do we bind them together? We need a new operation that let’s us combine things:

class Applicative f => Monad f where
  (>>=) :: f a -> (a -> f b) -> f b

Using this operation, we can easily define what we’re looking for:

instance Monad Parser where
  -- (>>=) :: Parser a -> (a -> Parser b) -> Parser b
  p1 >>= k = Parser $ \s ->
    case parse p1 s of
      Just (v,s') -> parse (k v) s'
      Nothing -> Nothing

lang :: Parser [Int]
lang = count >>= list

Other Monad instances

instance Monad Maybe where
  (Just v) >>= k = k v
  Nothing  >>= _ = Nothing
         
instance Monad (Either e) where
  (Right v) >>= k = k v
  (Left e)  >>= _ = Left e

We compared our various functions, using (=<<) :: Monad f => (a -> f b) -> f a -> f b a/k/a “reverse bind” for better symmetry:

($)   ::                    (a ->   b) ->   a ->   b  -- a/k/a apply
(<$>) :: Functor f =>       (a ->   b) -> f a -> f b  -- a/k/a fmap
(<*>) :: Applicative f => f (a ->   b) -> f a -> f b  -- a/k/a ap
(=<<) :: Monad f =>         (a -> f b) -> f a -> f b  -- a/k/a reverse bind

Recall that Monad is a sub-class of Applicative, and Applicative is a sub-class of Functor. Each adds expressivity: it’s possible to define (<*>) using (>>=) or (=<<) and pure; it’s possible to define (<$>) using (<*>) and pure.

We briefly mentioned an alternative operation, join :: Monad f => f (f a) -> f a. We’ll see that join and (>>=) are equivalent—each can encode the other.

The State monad

As a warmup to understanding how IO and state work in Haskell, we defined our own notion of “state”. A stateful computation is a function that takes a state s and returns a new state of type s and some value of type a.

newtype State s a = State { runState :: s -> (s,a) }

evalState :: State s a -> s -> a
evalState sa s = snd $ runState sa s

It turns out that this notion of state admits Functor, Applicative, and Monad instances.

instance Functor (State s) where
  fmap f sa = State $ \s ->
    let (s',a) = runState sa s in
      (s',f a)

instance Applicative (State s) where
  pure a = State $ \s -> (s,a)

  sf <*> sa = State $ \s ->
    let (s',f) = runState sf s
        (s'',a) = runState sa s' in
      (s'', f a)

instance Monad (State s) where
  sa >>= k = State $ \s ->
    let (s',a) = runState sa s in
      runState (k a) s'

We can define some State-specific primitive for working with our state:

get :: State s s
get = State $ \s -> (s,s)

set :: s -> State s ()
set s = State $ \_ -> (s,())

And now here’s a stateful implementation of factorial:

fact :: Int -> State (Int,Int) Int
fact n =
  set (1,n) >>
  factLoop >>
  get >>= \(acc,_) ->
  return acc
  where factLoop =
          get >>= \(acc,n) ->
          if n <= 0
          then return ()
          else
            set (n*acc,n-1) >>
            factLoop

NB that this cmoputation doesn’t actually mutate any state—we’re just defining functions. But we can write something that looks like a stateful computation, which may be nice.

The IO monad

We learned that main :: IO () is the entry point for Haskell programs, playing around with some basic IO actions:

main = putStr "What's your name? " >> hFlush stdout >> getLine >>= \s -> putStrLn ("Hello, " ++ s ++ "!")

We also played with IORef a, the type of references, i.e., mutable variables.

refs = newIORef True >>= \ref -> 
       writeIORef ref False >> 
       readIORef ref

But, dangerously, you’ll get the following in GHCi:

let a = newIORef True
a >>= \ref -> writeIORef ref False -- set the ref?
a >>= readIORef -- yields True! what?!
a >>= \ref -> writeIORef ref False >> readIORef ref -- yields False

The issue is one of staging: a value of type IO a hasn’t actually performed the action—it’s a script or recipe for the actions to be performed. The recipe for a above can be used more than once, but each time we’re composing recipes, not computations. That is, a is a recipe that allocates a new reference cell that holds booleans, with True as its initial value.

The first command we actually run, a >>= \ref -> writeIORef ref False yields a new recipe, where we allocate the cell and then write False to it. Haskell runs this recipe, allocating a new cell and writing to it. So far so good. Our second recipe allocates a new cell (with True in it) and reads from it. The first recipe has no bearing whatsoever on this second recipe. If we wanted the written and read reference cells to be related, we have to carefully do so, as in the third recipe.

do notation

                             do
action1 >>= \res1 ->   VS      res1 <- action1
action2 >>                     action2
let x = g res1 in              let x = g res 1
action3 >>= \res3 ->           res3 <- action3
action4 (f g res3)             action4 (f g res3)
fact' :: Int -> State (Int,Int) Int
fact' n = do
  set (1,n)
  factLoop
  (acc,_) <- get
  return acc
  where factLoop = do
          (acc,n) <- get
          if n <= 0
          then return ()
          else do
            set (n*acc,n-1)
            factLoop
main = do
  putStr "What's your name? "
  hFlush stdout
  s <- getLine
  putStrLn ("Hello, " ++ s ++ "!")

refs = do
  ref <- newIORef True
  writeIORef ref False
  readIORef ref