Monads for functional programming

Pedro Vasconcelos, DCC/FCUP

March 2021

Biblography

“Monads for functional programming”, Philip Wadler, 2001. PDF

Monads for functional programming

What is a Monad?

return :: a -> M a
(>>=) :: M a -> (a -> M b) -> M b

Monads in Haskell

The monad operations are overloaded in a type class:

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

-- NB: `m' is a *type constructor* not a *type*
-- i.e. m :: * -> *

Monad laws

For something to be a monad return and >>= must also satisfy three properties (“laws”).

Left-identity

return a >>= f \(\quad=\quad\) f a

Right-identity

m >>= return \(\quad = \quad\) m

Associativity

(m >>= f) >>= g \(\quad =\quad\) m >>= (\x -> f x >>= g)

NB: the compiler does not check this.

The partiality monad

The Maybe type

data Maybe a = Nothing | Just a

A value of type Maybe a is either:

Nothing

representing the absence of further information;

Just x

with a further value x :: a

Examples

Just 42 :: Maybe Int
Nothing :: Maybe Int

Just "hello" :: Maybe String
Nothing      :: Maybe String

Just (42, "hello") :: Maybe (Int,String)
Nothing            :: Maybe (Int,String)

Representing failure

Partial functions can return a Maybe value:

-- Example: lookup a key in key-value list
-- (from the Prelude)
lookup :: Eq a => a -> [(a,b)] -> Maybe b 
lookup k ((x,v):assocs)
   | k == x    = Just v  -- key found 
   | otherwise = lookup k assocs
lookup k []    = Nothing -- key not found

Representing failure (2)

phonebook :: [(String, String)]
phonebook = [ ("Bob",   "01788 665242"),
              ("Fred",  "01624 556442"),
              ("Alice", "01889 985333"),
              ("Jane",  "01732 187565") ]

E.g.:

> lookup "Bob" phonebook
Just "01788 665242"
> lookup "Alice" phonebook
Just "01889 985333"
> lookup "Zoe" phonebook
Nothing

Combining lookups

Lookup up a name…

  1. first in the phonebook
  2. then in an email list

Return the pair of phone, email and fail if either lookup fails.

Combining lookups (2)

getPhoneEmail :: String -> Maybe (String,String)
getPhoneEmail name =
   case lookup name phonebook of
     Nothing -> Nothing
     Just phone -> case lookup name emails of
        Nothing -> Nothing
        Just email -> Just (phone,email)


This works but gets very verbose quickly!

Monads to the rescue

We can simplify this pattern because Maybe is a monad.

-- define in the Prelude
instance Monad Maybe where
   return x      = Just x
   Nothing >>= k = Nothing
   Just x  >>= k = k x

Specific types of the monad operations:

return :: a -> Maybe a
(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b 

Re-writing the combined lookup

The code gets much shorter with >>= handling the failure cases.

getPhoneEmail :: String -> Maybe (String,String)
getPhoneEmail name =
   lookup name phonebook >>= \phone ->
   lookup name emails >>= \email ->
   return (phone,email)

Re-writing the combined lookup

Gets even simpler by using “do” notation.

getPhoneEmail :: String -> Maybe (String,String)
getPhoneEmail name
  = do phone <- lookup name phonebook
       email <- lookup name emails
       return (phone,email)

Exercise

Verify the monad laws for the Maybe monad instance.

The list monad

Non-deterministic computations

We can model computations yielding multiple answers in Haskell by returning a list of alternatives.

A non-deterministic computation from As giving Bs becomes a function A -> [B].

Example

List pairs of dice values that sum a given number.

A solution using a list comprehension:

dice_sum :: Int -> [(Int,Int)]
dice_sum k
 = [(d1,d2) | d1<-[1..6], d2<-[1..6], d1+d2==k]

Example:

> dice_sum 7
[(1,6),(2,5),(3,4),(4,3),(5,2),(6,1)]

The list monad

instance Monad [] where
   -- in the Prelude
   return x = [x]
   m >>= k  = [y | x<-m, y<-k x]
   -- alternative (equivalent) definition:
   -- m >>= k = concatMap k m

The specific types in this instance are:

return :: a -> [a]
(>>=)  :: [a] -> (a -> [b]) -> [b]

Re-writing the example

Non-deterministic computations can be also written in monadic style because lists are monads.

dice_sum :: Int -> [(Int,Int)]
dice_sum k = [1..6] >>= \d1 ->
             [1..6] >>= \d2 ->
             if d1+d2==k then 
                return (d1,d2)
             else []

Guards

Let us put the condition checking into a separate function:

dice_sum :: Int -> [(Int,Int)]
dice_dum k = [1..6] >>= \d1 ->
             [1..6] >>= \d2 ->
             guard (d1+d2==k) >>
             return (d1,d2)

guard :: Bool -> [()]
guard True  = return ()
guard False = []

Using “do” notation

Finally, we rewrite the monadic binds using do-notation.

dice_sum :: Int -> [(Int,Int)]
dice_dum k = do d1 <- [1..6]
                d2 <- [1..6]
                guard (d1+d2==k)
                return (d1,d2)


NB: we will later see that guard can be generalized to some (but not all) other monads.

Monad laws

Proving the monad laws we need more work than previously:

The error monad

Representing errors

If we need represent computations that may result in distinct errors we can use an Either result value:

-- from the Prelude
data Either a b = Left a | Right b


We can use:

Example

Write an integer division function that may fail because:

Example (cont.)

myDiv :: Int -> Int -> Either String Int
myDiv x y
    | y == 0       = Left "zero division"
    | x`mod`y /= 0 = Left "not exact"
    | otherwise    = Right (x`div`y)

> myDiv 42 2
Right 21
> myDiv 42 0
Left "zero division"
> myDiv 42 5
Left "not exact"

Monad instance for Either

As with Maybe, there is a monad instance in the Prelude for Either.

-- in the Prelude
instance Monad (Either e) where 
   return x      = Right x
   Left e >>= k  = Left e
   Right x >>= k = k x


Idea: Left values behave similiarly to exceptions.

Note that Either e is a monad but Either itself is not a monad (wrong kind).

Examples

> Right 41 >>= \x -> return (x+1)
Right 42

> Left "boom" >>= \x -> return (x+1)
Left "boom"

> Right 100 >>= \x -> Left "no way!"
Left "no way!"


Exercise: prove the monad laws for the Either instance.

The state monad

Representing stateful computations

Recall that we can view stateful computations as functions:

\[ \text{state} \longrightarrow (\text{result}, \text{new state}) \]

Example: random numbers


data StdGen  -- pseudo-random generator
             -- from System.Random

mkStdGen :: Int -> StdGen
             -- initialize a generator      

next :: StdGen -> (Int, StdGen)
             -- get next value and generator

Generate a random list

randomList :: Int -> StdGen -> ([Int], StdGen)
randomList 0 g = ([], g)
randomList n g | n>0
   = let (x, g1) = next g
         (xs,g2) = randomList (n-1) g1
     in (x:xs, g2)

Generate a random list (2)

The state monad

--- from Control.Monad.State

newtype State s a = State (s -> (a, s))
  -- type for state computations

run :: State s a -> s -> (a, s)
run (State f) s = f s

instance Monad (State s) where
   return a = State (\s -> (a, s))
   m >>= k  = State (\s ->
                 let (x, s') = run m s
                 in run (k x) s')

Random list with state monad

randomInt :: State StdGen Int
randomInt = State next

randomList :: Int -> State StdGen [Int]
randomList 0
  = return []
randomList n | n>0
  = do x <- randomInt
       xs<- randomList (n-1)
       return (x:xs)

State operations

State operations (2)

-- from Control.Monad.State

get :: State s s         -- get the state
get = State (\s -> (s, s))

put :: s -> State s ()   -- set the state
put s = State (\_ -> ((), s))

modify :: (s -> s) -> State s ()
         -- state-change using a function
modify f = State (\s -> ((), f s))

Example: a stack machine

Implement a simple stack machine with four instructions:

(The operations pop two values from the stack and push the result.)

Minimal stack machine

type Stack = [Int] -- type for stack of Int

push :: Int -> State Stack ()
push x = do xs<-get; put (x:xs) 

pop :: State Stack Int
pop = do (x:xs)<-get; put xs; return x

add, mult :: State Stack ()
add = do x<-pop; y<-pop; push (x+y)
mult = do x<-pop; y<-pop; push (x*y) 

Sample program

myprog :: State Stack Int
myprog = do push 2
            push 3
            add
            push 5
            mult
            pop

Running on an empty stack:

ghci> run myprog []
(25, [])

Exercise

Verify the monad laws for the state instance.

Reader and Writer

Reader monad

Special case of read-only state (e.g. environment)

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

instance Monad (Reader e) where
   return x = Reader (\_ -> x)
   m >>= k = Reader (\e -> let x = runReader m e
                           in runReader k x)

-- get the current environment
ask :: Reader e e 
-- execute a computation with a modified environment
local :: (e -> e) -> Reader e a -> Reader e a

(Cue example.)

Writer

Monoids

A set with an operation \(\star\) and an empty value \(u\) such that:

Examples:

The Monoid class

class Monoid m where
   mempty :: m           -- empty value
   mappend :: m -> m -> m  -- operation
   
instance Monoid [a] where
   mempty = []
   mappend = (++)

instance (Monoid a, Monoid b) => Monoid (a,b) where
   mempty = (mempty,mempty)
   mappend (x,y) (x',y') 
          = (mappend x x', mappend y y')

More monoid instances

-- for distinguishing the number instances 
newtype Sum a = Sum a

newtype Product a = Product a

instance Num a => Monoid (Sum a) where
   mempty = Sum 0
   mappend (Sum x) (Sum y) = Sum (x+y)

instance Num a => Monoid (Product a) where
   mempty = Product 1
   mappend (Product x) (Product y) = Product (x*y)

Monoid laws

For all x, y and z:

-- (1) neutral element
x `mappend` mempty 
       = mempty `mappend` x
       = x

-- (2) associativity
(x `mappend` y) `mappend` z 
       = x `mappend` (y `mappend` z) 

Writer monad

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

instance Monoid w => Monad (Writer w) where
    return x = Writer (x, mempty)
    m >>= k = let (x,w) = runWriter m
                  (y,w')= runWriter (k x)
              in (y, mappend w w')
    
-- log some output  
tell :: w -> Writer w ()
tell w = Writer ((), w)

(Cue example.)

Monads with plus

Failure and choice

Monads like lists support failure and choice; such operations are generalized in the MonadPlus class:

class Monad m => MonadPlus m where
  mzero :: m a
  mplus :: m a -> m a -> m a

MonadPlus instances

The instance for lists is straighforward:

instance MonadPlus [] where
   mzero = []
   mplus = (++)

MonadPlus instances (2)

There is also a MonadPlus instance for Maybe:

instance MonadPlus Maybe where
   mzero = Nothing
   Just a  `mplus` _ = Just a 
   Nothing `mplus` m = m

Examples

> Just 42 `mplus` Just 1
Just 42
> Nothing `mplus` Just 1
Just 1
> Nothing `mplus` Nothing
Nothing

A longer example

Given a name, get an email:

  1. first lookup in a personal list of emails;
  2. if that fails, lookup in the departmental list;
  3. if that fails, lookup in the colaborators list;
  4. if that fails, then the entire search fails.

A longer example (2)

personalEmails    :: [(Name, Email)]
departmentEmails  :: [(Name, Email)]
colaboratorEmails :: [(Name, Email)]
...

-- from the Prelude
-- lookup :: Eq a => a -> [(a,b)] -> Maybe b

searchEmail :: Name -> Maybe Email
searchEmail name =
    lookup name personalEmails  `mplus`
    lookup name departmentEmails `mplus`
    lookup name colaboratorEmails

Generic MonadPlus functions

-- from Control.Monad
-- `guard' fails if the condition is false;
-- otherwise does nothing
guard :: MonadPlus m => Bool -> m ()
guard True  = return ()
guard False = mzero

-- `msum` accumulates results with `mplus`
-- generalize the list-based `concat`
msum :: MonadPlus m => [m a] -> m a
msum = foldr mplus mzero

MonadPlus laws

The monad plus and zero operations should satisfy some laws:

Monoid

mplus and mzero should form a monoid (i.e. mplus is associative and mzero is an identity element)

Left Zero

mzero >>= k \(\quad=\quad\) mzero

There are proposals for further laws but unfortunately there is no consensus about them in the Haskell comunity: https://wiki.haskell.org/MonadPlus