How you should(n’t) use Monad

I’m often surprised by the fact that many people see monads as the be all and end all of Haskell’s abstraction techniques. Beginners often struggle over them thinking that they’re something incredibly important and complex. In reality though, monads are neither important, nor complex, and that’s what I aim to show with this little tutorial about what other abstraction techniques you can use, and when they’re appropriate.

First things first – IO

The reason a lot of people come across monads is that they want to get on with interacting with the outside world – they want to do I/O. I’m going to get this out of the way quickly. In Haskell, IO is kept in a carefully constrained box, because unconstrained it violates referential transparency (that is, you can get multiple answers from the same call to the same function depending on what the user happens to type/how they wibble the mouse/etc). You can recognise functions in this box by their type signature – they involve a type that looks like this: IO something.

Here’s a few examples:

-- Call this, and you get back a Char,
-- carefully wrapped up in an IO type.
getChar :: IO Char
-- This one doesn't have an interesting result,
-- only a unit value wrapped up in an IO type.
putStrLn :: String -> IO () 

These can be stuck together with the handy do notation:

main = do
  putStrLn "What is your name?"
  name <- getLine
  putStrLn ("Your name is " ++ name)

There, that’s that out of the way – we can do IO now, and we didn’t need to understand anything nasty or complex.

Some Abstraction techniques – Dealing with values in boxes

We often deal with values that are hidden inside other types. For example, we use lists, to hide values in, we use Maybes etc. What would be nice, is if we could apply a function to the values hiding in those boxes. Early in learning Haskell I’m sure you will have met a function that can do this for lists: map. This can be generalised though: Enter the Functor. Functors can do one thing, and one thing only, they can apply a function to a value inside an outer construction. They do this with the function fmap (or Functor map). Lets look at some examples:

For Lists, fmap is simply map:

> fmap (+1) [1,2,3,4]
[2,3,4,5]

For Maybe values fmap lets us apply a function to the value inside a just:

> fmap (+1) (Just 1)
Just 2
> fmap (+1) Nothing
Nothing

For Tuples, fmap lets us apply a function to the second half of the tuple (if we import an extra module that defines it):

> import Control.Applicative
> fmap (+1) (1,2)
(1,3)

We can use fmap to target a function into several layers of boxes by composing applications:

> (fmap . fmap) (+1) [(1,2), (3,4)]
[(1,3),(3,5)]

Here, the first fmap pushes (fmap (+1)) inside the list, and the second fmap pushes (+1) inside the tuples.

Putting things in boxes

All that isn’t very useful if we can’t actually put something in a box in the first place. This is where the pure function comes in handy. This function lets us wrap anything we like in a box.

> pure 1 :: [Int]
[1]
> pure 1 :: Maybe Int
Just 1
> pure 1 :: Either String Int
Right 1

In Haskell, the pure function is in the Applicative class (you’ll need to import Control.Applicative). The Applicative class does some other interesting things as we’ll see in a minute. Because of this it would be nice if pure were separated into its own little class all on its own, but unfortunately that isn’t the way it is in Haskell (at the moment at least).

Boxes everywhere

So, we’ve seen how to put something in a box, and we’ve seen how to apply a function to a value in a box, but what if our function is in a box too? At this point, the Applicative class really comes into its own. The (<*>) function from Applicative lets us apply boxes to each other as long as they have the right types of values inside.

> (Just (+1)) <*> (Just 1)
Just 2
> [(+1), (*2), (^3)] <*> [1,2,3]
[2,3,4,2,4,6,1,8,27]

That second result is not entirely clear – what’s going on? Well, the (<*>) function has applied each function to each argument in turn, and bundled up all the results in one list. (+1) gets applied to each argument, generating the results 2,3 and 4; (*2) gets applied to each argument, generating the results 2,4 and 6; and finally (^3) gets applied to each argument, generating the results 1,8 and 27.

An important note: All Applicatives are also Functors. You can implement fmap for any Applicative like this:

fmap f a = (pure f) <*> a

Applicative in fact does this for you, but calls the function (<$>).

Functions that produce boxes

When we have functions that produce values that are hidden inside boxes, we have a problem. Each time we apply the function we get an additional layer of boxes, this isn’t particularly pretty, nor composable. This is where monads come in. Monads add a single function called join, which is used to flatten out the layers of boxes:

> join (Just (Just 2))
Just 2
> join [[1],[2],[3,4,5]]
[1,2,3,4,5]

The join function lets us compose our box-producing functions more easily. We now fmap our box producing function over values in a box. This results in a 2-layer set of boxes. We can then use join to squash that back down again. This pattern is so useful that we call it “bind” or (=<<).

f =<< a = join (f <$> a)

Some people like to define this the other way round:

a >>= f = join (f <$> a)

This allows a very imperative style of programming where we ask the language to take the result of one computation, push it through a function, take the results, push them through another function, etc.

As with Applicatives and Functors, all Monads are Applicatives. We can define the (<*>) function using only bits of a Monad and the pure function:

f <*> a = f >>= (\fv -> a >>= (pure . fv))

We can see here a common pattern with monadic programming. We bind a function returning a monadic value into a lambda. Haskell provides a syntactic sugar for doing this called do notation:

f <*> a = do
  fv <- f
  av <- a
  pure (fv av)

We can now see clearly that IO in Haskell is not using any magic at all to introduce an imperative concept to a functional language, instead the IO type is simply a monad. Remember, this means that it’s a functor and an applicative too, so we can use <$> and <*> wherever we please in IO code to apply functions to IO values.

Why you don’t always want to go for Monads

As we’ve seen, Monad sits atop a set of classes proudly the most powerful of all, but that doesn’t mean we want to use it all the time. As we’ve seen, Monad gives us a very imperative feel to our code – it reveals an order that isn’t necessarily there. Do notation particularly seems to suggest (in our example above) that we should first take the value out of f, then take the value out of a, and then apply the two. In reality, this order is not there, the Haskell runtime is free to evaluate these in any order it likes. This can make such language constructs dangerous. Firstly, we’re functional programmers because we like describing what things “are”, not what steps you should take to produce them. Secondly, the steps we seem to give here, are not the ones that the run time will really take in the end.

Lets look at an example of when we really shouldn’t use Monads. We have excellent Parser combinators in the Parsec library. These let us define small parsers, and stick them together using the Monadic interface. Lets define a small parser to parse an Int that may or may not be in a string:

parseInt = do
  ds <- many1 digit
  pure $ read ds

parseMaybe p =
      (do n <- p
          pure (Just n))
  <|> (pure Nothing)

We are expressing an ordering that we don’t intend to – first we accept at least one digit into ds, then we read them and rewrap them in a parser. In parseMaybe first we parse something, and take the value out into n, then we wrap it in Just, and give it back.

This isn’t clear. Why couldn’t we just describe the grammar? Why do we have to specify an order? Lets patch parsec to provide an Applicative instance:

instance Applicative (GenParser a st) where
  (<*>) = ap
  pure = return

Note that I’m using a shorter version of the definition of (<*>) in a monad using the ap function. Now we may use the applicative functor interface:

parseInt = read <$> many1 digit

parseMaybe p = (Just <$> p) <|> (pure Nothing)

Not only are these definitions shorter, but we can quickly and easily see their meanings – an integer is many digits, with read applied to get them into a form we can use in Haskell.

Lets look at a more complex example:

data Record = R { firstCol, secondCol :: Maybe Int }
              deriving (Show)

parseRecord = do
  col1 <- parseMaybe parseInt
  char ','
  col2 <- parseMaybe parseInt
  char '\n'
  pure (R col1 col2)

Again, we’re specifying an order we don’t want to see. Lets look at this in applicative style:

parseRecord =
  R <$> (parseMaybe parseInt <* char ',')
    <*> (parseMaybe parseInt <* char '\n')

Note the use of the (<*) function – this simply takes the value from the left hand parser, and passes it up, ignoring the value returned by the right hand parser. We can now see that parseRecord constructs a record from two maybe Ints, separated with a comma. We haven’t introduced any orderings that we don’t need to, and we’ve even condensed our code a little.

Conclusions

We’ve seen the hierarchy of classes in Haskell in all its glory, rather than focusing unduly on the Monad, we’ve seen that the Monad interface, while powerful, is not always desirable. Hopefully we’ve seen that a lot of our monadic code can be cleaned up to use the Applicative (or maybe even Functor) interface instead.

22 comments on “How you should(n’t) use Monad

  1. jberryman says:

    Nice post, thanks. OT: what do you use to highlight your code snippets?

  2. ___ says:

    The fmaps in your definitions of (=<>=) are missing. Looks like they were taken out by your blog software.

  3. ___ says:

    Heh. Happened to me, too. That’s supposed to be the bind and flip bind functions.

  4. crooney says:

    Wow. That was a great article. I’ve read it through twice now, and feel much enlightened.

    3 nitpicks, which I think will make it even easier to grok:

    fmap (+1) (1,2) requires an unmentioned Control.Monad.Instances.

    the sentence
    ‘Firstly, we’re functional programmers because we like describing what things “are” not what steps you should take to produce them.’
    needs a comma after “are” or is extremely difficult to parse.

    Lastly in the parser part from Alternative is used unannounced, in code intended to demonstrate superior simplicity to do notation. Only takes a few moments of hayooing to understand it, but it could be mentioned.

    Be clear, i’m not complaining. This is the most cogent thing i’ve ever read about applicatives, and one of the most on any non-trivial haskell subject.

    FWIW, your thoughts on the GPL are sound, also.

    thanks again

    • beelsebob says:

      Thanks for the comment, A quick note – <|> is also available in Text.ParserCombinators.Parsec, though it’s exactly the same as the Control.Applicative version. Mostly I was too lazy to show how to write the Alternative instance, perhaps I should.

      Bob

  5. crooney says:

    OK, wordpress ate my symbol — i meant the “associative binary operation” for Alternative. i don’t know how to escape it and don’t want to leave 7 comments trying.

    ta

  6. niv says:

    I’m not sure if I agree with the parser example: you DO want to see the order in the parsing, if you change the order the parser behaves completely different.
    When you write “(parseMaybe parseInt <* char ‘,’) (parseMaybe parseInt <* char ‘\n’)”, the order is totally there, it’s “int-comma-int-newline”! You’re relying on the fact that the “application” works from left to right.

    • beelsebob says:

      Indeed, I agree that there is order that you want to see in the parser – you want to see the order that the grammar defines things to occur in. What you don’t want to see though is a supposed order that evaluation will happen in, or a supposed order that the parser will work in. You don’t want to see “this parser should first parse a maybe int” because it’s entirely possible that tomorrow someone will come up with a parsing technique that works backwards/forwards/in some random other order.

      Essentially, we want to see only the language grammar, and not that the parser itself has to follow the order in the language’s grammar.

  7. […] How you should(n’t) use Monad I’m often surprised by the fact that many people see monads as the be all and end all of Haskell’s […] […]

  8. Good post! I’m using Applicative now in my SQL parser, and it actually makes the code clearer and easier to read.

  9. Ben Franksen says:

    Great Post.

    There is a small error: “fmap f a = (pure f) a
    Applicative in fact does this for you, but calls the function ().”

    As the docs say, is just a synonym for fmap, so you cannot use it to define fmap. Instead use liftA, citing from the docs:

    “liftA :: Applicative f => (a -> b) -> f a -> f b
    Lift a function to actions. This function may be used as a value for fmap in a Functor instance.”

    Cheers
    Ben

  10. Ex Girlfiend says:

    My fellow on Orkut shared this link with me and I’m not dissapointed at all that I came to your blog.

  11. This is very up-to-date info. I’ll share it on Twitter.

  12. “As we’ve seen, Monad gives us a very imperative feel to our code – it reveals an order that isn’t necessarily there. Do notation particularly seems to suggest (in our example above) that we should first take the value out of f, then take the value out of a, and then apply the two. In reality, this order is not there, the Haskell runtime is free to evaluate these in any order it likes. ”

    This is wrong. The Haskell runtime is not free to run monadic functions in an arbitrary order. That is part of the point of a monad. The bind function, and the notion of “beta-reduction” is sufficient proof. Look at the type of the bind function:

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

    It takes an M container, and a function on the underlying type. Indeed, the bind operator “binds” the first container’s value to the function’s free variables.

    In particular, this means that the M a container/computation has to occur first in the “real” computation as done by a machine. In order to compute the value of (M a) >>= f, you need to know what a is, as a value, just as you need to know what a is before you can compute f $ a. do notation could be the cause of your confusion, but consider that

    do
    x <- (MonadInstance a)
    y >= (\x -> ((MonadInstance a) >>= \y -> return (x + y))

    In principle, x <- (MonadInstance a) could be computed before or after y >, >>=, and lambda binding make it impossible. In general,

    (MonadInstance a) >>= (\x -> ((MonadInstance a) >>= \y -> return (f x y))

    and

    (MonadInstance a) >>= (\y -> ((MonadInstance a) >>= \x -> return (f x y))

    do not evaluate to the same values. But sometimes they do, which makes the problem undecidable. The compiler can’t just optimize the binding order even when they are formally equivalent, since it usually can’t tell *that* they are formally equivalent. In this example, f would have to be commutative, or (MonadInstance a) >>= would have to be a constant function. The compiler can’t determine either of those, in general.

    It is true that a monad “enforces” an order that isn’t necessarily natural. But every computation must be sequenced in order to run. So there must be a “concrete” or “abstract” monad “somewhere”. In Haskell, the IO monad does the first layer of this sequencing, and any monads used within functions called by main() will do sub-sequencing, as will plain old beta-reduction.

    I don’t want to pooh-pooh your fine article, especially since it helped my intuition about monads as a generalization of a topological/lattice closure operator. I am working on “putting it all together” too.

    • beelsebob says:

      Monads are free to be lazy whenever they like. See the IO monad for example. Here’s a simple lazy monad:
      data A a = A a
      monad A where
      return = A
      (A x) >>= f = f x
      The A must be forced, but that doesn’t mean that the value inside it must be.

      Bob

      • It seems that the example I typed up broke. I meant:

        do
        x <- MonadInstance a
        y >= ( \x -> (MonadInstance b >>= ( \y -> ( return x + y )))

        If this code runs at all, the function bindings force the order of evaluation.

        Even if the runtime is making promises (thunks in Haskell-speak), it is going to have have to unroll those promises and compute x before it can compute f x in a computation (A x) >>= f. There’s just no way around that. If an operation is going to occur at all, laziness can’t change the order in which its sub-operations occur. It merely means that the runtime performs computations on demand.

        Beta reduction is what allows different computational orders, depending on the functional argument dependency tree. For example, in the computation f (g x) (h y), (g x) or (h y) can be computed first, but they BOTH have to be computed before f (g x) (h y) (the whole thing).

        But the whole point of a monad is that the monadic combinators bind the output of one computation to the input of a one argument function. There is no ambiguity about the order of f $ g $ h $ i $ k, and laziness will not change the order in which these functions are called. k goes first. The monadic combinators have semantics similar to the application operator $.

        http://en.wikipedia.org/wiki/Beta_reduction

        Also note the Control.Monad documentation (http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Monad.html#v%3A%3E%3E%3D), which describes the semantics of >>= and >> as:

        (>>=) Sequentially compose two actions, passing any value produced by the first as an argument to the second.

        (>>) Sequentially compose two actions, discarding any value produced by the first, like sequencing operators (such as the semicolon) in imperative languages.

        Laziness does not change the order in which operations occur. Beta-reduction (what the Haskell literature calls “non-strict reduction” or “evaluation”) is what does that. These are related but NOT synonymous. You can have an eager, non-strict language. Or lazy and strict semantics. A web server like Apache is lazy and potentially strict as a computational system, since it lazily dispatches requests to a runtime of your choice.

        http://www.haskell.org/haskellwiki/Lazy_vs._non-strict

        • beelsebob says:

          let x = undefined; f = const (return 5)
          in (A x) >>= f

          (A undefined) >>= const (return 5)
          { evaluate application of >>= }
          ~> const (return 5) undefined
          { evaluate application of const }
          ~> return 5
          { evaluate application of return }
          ~> 5

          The evaluation order is *not* fixed by the monad. There is no constraint here that x must be evaluated before being passed to f.

        • beelsebob says:

          p.s. Sorry for not moderating your comment for a while – I didn’t get an email about it :/

  13. It broke again. Stupid less thans and greater thans.

    do
    x <- MonadInstance a
    y <- MonadInstance b
    return (x + y)

    is equivalent to

    MonadInstance a >>= ( \x -> (MonadInstance b >>= ( \y -> ( return x + y )))

Leave a reply to beelsebob Cancel reply