Monads and more

Remember the Maybe type

data Maybe a = Nothing
| Just a

We know that Maybe is a functor

data Maybe a = Nothing
| Just a

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

instance Functor Maybe where
fmap _ Nothing = Nothing
fmap f (Just a) = Just (f a)

What does fmap actually mean?

We have a polymorphic type f, and fmap gives us the ability to:

So what's f?

That polymorphic type f was daunting to me when I was learning Haskell.

The easiest easy to begin to think of f is as a "container".

Here is the most basic of containers:

newtype Container a = Container a

instance Functor Container where
fmap f (Container a) = Container (f a)

We can't get any simpler than this, since (being a newtype) it doesn't have a runtime representation at all.

More containers

instance Functor Container where
fmap f (Container a) = Container (f a)

instance Functor Maybe where
fmap _ Nothing = Nothing
fmap f (Just a) = Just (f a)

instance Functor [] where
fmap = map

Having seen these instances, we can now state with some confidence:

In other words, fmap will not turn a Just into a Nothing, or a 3-element list into an empty list, or the like.

Is that it?

As useful as this intuitive picture is, it's actually not general enough.

We'd be making a mistake if we thought we had the whole story now, because the truth is far richer (and stranger).

Functions

Let's poke about in ghci:

>> :type not
not :: Bool -> Bool

Remember that the -> symbol is not magic: it's just a type constructor.

Using a notational shortcut, we could rewrite the type above as:

(->) Bool Bool

If we get rid of the concrete types and replace them with polymorphic placeholders, we can write a type signature like this:

(->) a b

More fun with functions

Okay, so we know that this is a function type:

(->)

And this is a function that accepts an argument of some type a, and gives a result of some other type b:

(->) a b

So then what's this?

(->) a

Isn't that suggestive?

This type, being a function that accepts an argument of type a, is polymorphic. (Why?)

((->) a)

Which suggests that even though it's surely not a container type, we could write a Functor instance.

instance Functor ((->) a) where
fmap f {- ...what? -}

Stop! Hammer time!

On the whiteboard, let's puzzle through what the Functor instance ought to look like.

instance Functor ((->) a) where
fmap f {- ...what? -}

I hope you haven't peeked ahead!

Because here's that definition we were scrawling on the whiteboard.

instance Functor ((->) a) where
fmap f g = \x -> f (g x)

Which we can simplify to:

instance Functor ((->) a) where
fmap f g = f . g

And again:

instance Functor ((->) a) where
fmap = (.)

Wow. Wow!

Function application is somehow a functor?

I know, right!?

Let's play with that in ghci a bit.

So really, what's a functor?

A functor (in Haskell) is simply a pair of things:

The instance has to obey two simple laws:

fmap id      == id
fmap (f . g) == fmap f . fmap g

As usual with laws, it's up to you as a coder to satisfy the laws with your Functor instances.

The next step

In the Control.Applicative package we'll find another extremely useful typeclass:

class Functor f => Applicative f where

pure :: a -> f a

(<*>) :: f (a -> b) -> f a -> f b

The Applicative class builds on functors to add two very useful new behaviours.

Lifting again

If those definitions feel slippery, remember the signature for fmap:

fmap :: (a -> b) -> f a -> f b

The only difference between fmap and <*> is that <*> starts off with the function wrapped in the type f.

(<*>) :: f (a -> b) -> f a -> f b

This is easiest to follow with a concrete example.

instance Applicative Maybe where
pure = Just

Just f <*> Just a = Just (f a)
_ <*> _ = Nothing

Thinking about constraints

Which of these questions is easier to answer?

By adding more information, we've constrained the possible numbers available to be guessed.

We can loosely carry this line of thinking over to typeclasses:

Function application as an applicative functor

To keep those brains nice and groovy, let's look at how function application lives as an Applicative.

instance Applicative ((->) a) where
pure x = \_ -> x

f <*> g = \x -> f x (g x)

Functor vs Applicative

The Functor class has one method and two laws.

The Applicative class adds two methods and four laws (the laws are simple and intuitive, but I'm not going to describe them).

By appeal to my prior handwaving, the added richness of Applicative comes at a cost:

That richness is appealing though: we'll take it when we can. (But I'm not going to explain why just yet.)

Functor vs Applicative, revisited

An applicative is once again a triple of things:

And the definitions have to satisfy the aforementioned four laws (which you can look up for yourself).

And on to monads

Monads represent another step up the ladder of richness from applicative functors.

This is, of course, thanks to the bind operator.

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

We've already used this operator aplenty, but even so, we lacked the background to discuss why it matters.

What we gain with a bind operator

Here's a piece of code that we simply can't express using only the Functor or Applicative machinery:

oddEnough act = do
v <- act
if odd v
then fail "too odd!"
else return v

Neither fmap nor <*> lets us "change the shape" of the outcome of a series of operations, but >>= does.

To make that more concrete:

Some examples

Here's a standard function that takes a predicate expression and an action, and executes the action only if the predicate succeeds:

when :: (Monad m) => Bool -> m () -> m ()
when p act = if p then act else return ()

Notice that we've defined a very handy control flow function that will work in all monads.

Suppose we want to perform an action that returns a success/fail indication, and use that result to determine whether to perform a second action.

whenM :: (Monad m) => m Bool -> m () -> m ()

Let's write out a body for this function.

Tantalizing hints

Here's a function from Control.Monad that we've seen before:

liftM :: Monad m   => (a -> r) -> m a -> m r

It bears a striking resemblance to this:

fmap  :: Functor f => (a -> b) -> f a -> f b

And here's a function we just met:

(<*>) :: Applicative f => f (a -> b) -> f a -> f b

Which looks very similar to this Control.Monad combinator:

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

A little history

We've seen that Applicative is defined to be a subclass of Functor:

class Functor f => Applicative f {- ... -}

Shouldn't one of these hold, too?

class Functor m => Monad m {- ... -}

class Applicative m => Monad m {- ... -}

"Yes" in principle, but for historical reasons, "no".

Monads and functors were introduced to Haskell around the same time, and I'm not sure the possible relationship between them was recognized at the time.

Applicative functors arrived on the scene much later. By the time a possible resolution to the tangle was identified, there was too much code "in the wild" to change things.

Function application as a monad

Continuing our theme that just like functors and applicatives, monads are not limited to container types:

instance Monad ((->) r) where
-- same as the pure method of Applicative
return x = \_ -> x

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

Parsing

Suppose we want to parse part of a string.

We need to consume some - but probably not all - of the input, and return a result. Let's return the remainder of the input that we haven't consumed, so someone else can deal with it.

parse :: String -> (a, String)

Purely functional random numbers

Let's briefly get back to some material I didn't have time to cover a few weeks ago.

Haskell supplies a random package that we can use in a purely functional setting.

class Random a where
random :: RandomGen g => g -> (a, g)

class RandomGen g where
next :: g -> (Int, g)
split :: g -> (g, g)

"Modifying" state

Notice the similarities between these types:

random :: RandomGen g => g      -> (a, g)
parse :: String -> (a, String)

In each case, we emulate "state update" by returning a new state.

Yuck!

From that earlier lecture's unseen slides, recall that threading through all those updates is a pain:

guess :: (RandomGen g) => (Double,g) -> (Double,g)
guess (_,g) = (z, g'')
where z = x^2 + y^2
(x, g') = random g
(y, g'') = random g'

It would be really easy to reuse a piece of state by accident, and this is a very simple function!

A new look at state transformation

Here's our most general setting for those state transformation functions:

s -> (a,s)

If we pay no attention to the s parameter, we have one of the crucial criteria for being a Functor, Applicative, or Monad:

What about the rest?

A little protection

It would actually be a bad thing if we were to declare this type to be a Functor:

s -> (a,s)

Why? It would overlap with the Functor instance for ((->) a).

To avoid the potential for overlapping instances, we wrap up our state transformation type in a newtype.

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

A Functor instance

instance Functor (State s) where
fmap f (State action) = State $ \origState ->
let (a, newState) = action origState
in (f a, newState)

The nice thing about our state transformer is that it works over all states. Some examples include:

And a Monad instance

instance Monad (State s) where
return a = State $ \s -> (a, s)

State act >>= k = State $ \s ->
let (a, s') = act s
in runState (k a) s'

The bind operator simply passes the result of the first operation to the second.

Manipulating state directly

We can retrieve the current state by copying it into the result field of our pair.

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

If we want to replace the current state with a modified version, that's equally simple.

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

Before

Recall this function:

guess :: (RandomGen g) => (Double,g) -> (Double,g)
guess (_,g) = (z, g'')
where z = x^2 + y^2
(x, g') = random g
(y, g'') = random g'

With a little help

import System.Random
import Control.Monad.State

modify' :: MonadState s m => (s -> (a,s)) -> m a
modify' f = do
s <- get
let (a,s') = f s
put s'
return a

The MonadState class takes the State-specific methods, and makes them available for other monads to implement:

class (Monad m) => MonadState s m | m -> s where
get :: m s
put :: s -> m ()

Functional dependencies

Who noticed the vertical bar and arrow?

class (Monad m) => MonadState s m | m -> s {- ... -}

This is called a functional dependency. Fundeps are used to make type checking of multi-parameter type classes tractable.

This fundep tells the type checker (and us) that the type of the state parameter s can be determined from the type of the monad parameter m.

How does this work?

instance MonadState s (State s) where
get = State $ \s -> (s, s)
put s = State $ \_ -> ((), s)

Here, we're saying that the type State s is our monad, and the fundep ties its s parameter to the s parameter of the MonadState class.

A new guesser

Here's a rewrite of our earlier guess function to use the modify' function that we just wrote:

guess :: RandomGen g => State g Double
guess = do
a <- modify' random
b <- modify' random
return (a*a + b*b)

Notice that we've managed to completely hide the state of the PRNG!

Why functional dependencies?

Suppose we were to write a simpler multi-parameter type class, without the fundep:

class (Monad m) => MonadState s m {- ... -}

And if we were to try to typecheck these type signatures:

modify' :: MonadState s m => (s -> (a,s)) -> m a

guess :: RandomGen g => State g Double

Without the fundep, the compiler would choke on these, because it has no information to assure it that the g parameter to State is related to the s parameter to MonadState.

Using the state monad

Suppose we're running a social network, and we want to know who is connected to whom.

To build a matrix of connections, we need to represent user addresses as integer positions on each axis.

import Control.Applicative
import Control.Monad.State
import qualified Data.Map as Map

type Address = String

data Number = N !(Map.Map Address Int) !Int
deriving (Show)

The Number type is the state we'll use (and possibly modify) while numbering.

Getting started

This is the top-level address-numbering function.

renumber :: [(Address,Address)] -> [(Int,Int)]
renumber xs = evalState (mapM pair xs) (N Map.empty 0)
where pair (x,y) = (,) <$> number x <*> number y

This depends on a few functions we haven't seen before.

Monadic mapping:

mapM :: Monad m => (a -> m b) -> [a] -> m [b]

The second of the three "run me a state monad" functions:

runState  :: State s a -> s -> (a, s)
evalState :: State s a -> s -> a
execState :: State s a -> s -> s

The super-useful <$> operator is nothing but shorthand for fmap.

And finally, a use in the wild for the <*> operator!

What about the number function?

This is where the real work happens.

If an address is already stored in the numbering map, our function returns the number associated with the address.

number :: Address -> State Number Int
number addr = do
N numMap highest <- get
case Map.lookup addr numMap of
Just j -> return j
Nothing -> do let highest' = highest + 1
newMap = Map.insert addr highest numMap
put $! N newMap highest'
return highest'

Otherwise, we increment the highest number seen, associate the previous number with the address, store the modified state, and return the number.

The Reader monad

Reader is another widely used monad, and in fact we've already seen a form of it:

((->) a)

This is best understood in comparison to the state monad:

As an example of a piece of immutable data that we might want to thread around all over the place, think "application configuration".

The reader monad lets us hide the plumbing of passing that information around.

Reader vs reader

The Reader type is defined in Control.Monad.Reader.

The only difference between it and ((->) a) is that Reader is a newtype wrapper around ((->) a).