block by roachhd b473c3c9aa921d14563b

The Typeclassopedia from the Haskell wiki

% Typeclassopedia % Brent Yorgey

Originally published 12 March 2009 in issue 13 of the Monad.Reader. Ported to the Haskell wiki in November 2011 by Geheimdienst. Converted to Markdown in August 2013 by Erlend Hamberg. Converted to EPUB format with pandoc.

This is not the official version of the Typeclassopedia. The official version is now the Haskell wiki version which supersedes the version published in the Monad.Reader. Please help update and extend it by editing it yourself or by leaving comments, suggestions, and questions on the talk page.

Abstract

The standard Haskell libraries feature a number of type classes with algebraic or category-theoretic underpinnings. Becoming a fluent Haskell hacker requires intimate familiarity with them all, yet acquiring this familiarity often involves combing through a mountain of tutorials, blog posts, mailing list archives, and IRC logs.

The goal of this document is to serve as a starting point for the student of Haskell wishing to gain a firm grasp of its standard type classes. The essentials of each type class are introduced, with examples, commentary, and extensive references for further reading.

Introduction

Have you ever had any of the following thoughts?

If you have, look no further! You, too, can write and understand concise, elegant, idiomatic Haskell code with the best of them.

There are two keys to an expert Haskell hacker’s wisdom:

#. Understand the types. #. Gain a deep intuition for each type class and its relationship to other type classes, backed up by familiarity with many examples.

It’s impossible to overstate the importance of the first; the patient student of type signatures will uncover many profound secrets. Conversely, anyone ignorant of the types in their code is doomed to eternal uncertainty. “Hmm, it doesn’t compile … maybe I’ll stick in an fmap{.haskell} here … nope, let’s see … maybe I need another (.){.haskell} somewhere? … um …”

The second key—gaining deep intuition, backed by examples—is also important, but much more difficult to attain. A primary goal of this document is to set you on the road to gaining such intuition. However—

There is no royal road to Haskell. –Euclid ^[Well, he probably would have said it if he knew Haskell.]

This document can only be a starting point, since good intuition comes from hard work, not from learning the right metaphor. Anyone who reads and understands all of it will still have an arduous journey ahead—but sometimes a good starting point makes a big difference.

It should be noted that this is not a Haskell tutorial; it is assumed that the reader is already familiar with the basics of Haskell, including the standard Prelude, the type system, data types, and type classes.

The type classes we will be discussing and their interrelationships:

One more note before we begin. The original spelling of “type class” is with two words, as evidenced by, for example, the Haskell 2010 Language Report, early papers on type classes like Type classes in Haskell and Type classes: exploring the design space, and Hudak et al.’s history of Haskell. However, as often happens with two-word phrases that see a lot of use, it has started to show up as one word (“typeclass”) or, rarely, hyphenated (“type-class”). When wearing my prescriptivist hat, I prefer “type class”, but realize (after changing into my descriptivist hat) that there’s probably not much I can do about it.

We now begin with the simplest type class of all: Functor{.haskell}.

Functor

The Functor{.haskell} class (haddock) is the most basic and ubiquitous type class in the Haskell libraries. A simple intuition is that a Functor{.haskell} represents a “container” of some sort, along with the ability to apply a function uniformly to every element in the container. For example, a list is a container of elements, and we can apply a function to every element of a list, using map{.haskell}. As another example, a binary tree is also a container of elements, and it’s not hard to come up with a way to recursively apply a function to every element in a tree.

Another intuition is that a Functor{.haskell} represents some sort of “computational context”. This intuition is generally more useful, but is more difficult to explain, precisely because it is so general. Some examples later should help to clarify the Functor{.haskell}-as-context point of view.

In the end, however, a Functor{.haskell} is simply what it is defined to be; doubtless there are many examples of Functor{.haskell} instances that don’t exactly fit either of the above intuitions. The wise student will focus their attention on definitions and examples, without leaning too heavily on any particular metaphor. Intuition will come, in time, on its own.

Definition

Here is the type class declaration for Functor{.haskell}:

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

Functor{.haskell} is exported by the Prelude{.haskell}, so no special imports are needed to use it.

First, the f a{.haskell} and f b{.haskell} in the type signature for fmap{.haskell} tell us that f isn’t just a type; it is a type constructor which takes another type as a parameter. (A more precise way to say this is that the kind of f must be * -> *{.haskell}.) For example, Maybe{.haskell} is such a type constructor: Maybe{.haskell} is not a type in and of itself, but requires another type as a parameter, like Maybe Integer{.haskell}. So it would not make sense to say instance Functor Integer{.haskell}, but it could make sense to say instance Functor Maybe{.haskell}.

Now look at the type of fmap{.haskell}: it takes any function from a to b, and a value of type f a{.haskell}, and outputs a value of type f b{.haskell}. From the container point of view, the intention is that fmap{.haskell} applies a function to each element of a container, without altering the structure of the container. From the context point of view, the intention is that fmap{.haskell} applies a function to a value without altering its context. Let’s look at a few specific examples.

Instances

As noted before, the list constructor []{.haskell} is a functor ^[Recall that []{.haskell} has two meanings in Haskell: it can either stand for the empty list, or, as here, it can represent the list type constructor (pronounced “list-of”). In other words, the type [a]{.haskell} (list-of-a) can also be written [] a{.haskell}.]; we can use the standard list function map{.haskell} to apply a function to each element of a list ^[You might ask why we need a separate map{.haskell} function. Why not just do away with the current list-only map{.haskell} function, and rename fmap{.haskell} to map{.haskell} instead? Well, that’s a good question. The usual argument is that someone just learning Haskell, when using map{.haskell} incorrectly, would much rather see an error about lists than about Functor{.haskell}s.]. The Maybe{.haskell} type constructor is also a functor, representing a container which might hold a single element. The function fmap g{.haskell} has no effect on Nothing{.haskell} (there are no elements to which g can be applied), and simply applies g to the single element inside a Just{.haskell}. Alternatively, under the context interpretation, the list functor represents a context of nondeterministic choice; that is, a list can be thought of as representing a single value which is nondeterministically chosen from among several possibilities (the elements of the list). Likewise, the Maybe{.haskell} functor represents a context with possible failure. These instances are:

instance Functor [] where
  fmap _ []     = []
  fmap g (x:xs) = g x : fmap g xs
  -- or we could just say fmap = map

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

As an aside, in idiomatic Haskell code you will often see the letter f used to stand for both an arbitrary Functor{.haskell} and an arbitrary function. In this document, f represents only Functor{.haskell}s, and g or h always represent functions, but you should be aware of the potential confusion. In practice, what f stands for should always be clear from the context, by noting whether it is part of a type or part of the code.

There are other Functor{.haskell} instances in the standard libraries; below are a few. Note that some of these instances are not exported by the Prelude; to access them, you can import Control.Monad.Instances.

Exercises

#. Implement Functor{.haskell} instances for Either e{.haskell} and ((->) e){.haskell}. #. Implement Functor{.haskell} instances for ((,) e){.haskell} and for Pair{.haskell}, defined as data Pair a = Pair a a{.haskell}. Explain their similarities and differences. #. Implement a Functor{.haskell} instance for the type ITree{.haskell}, defined as

```haskell
data ITree a = Leaf (Int -> a)
             | Node [ITree a]
```

#. Give an example of a type of kind * -> *{.haskell} which cannot be made an instance of Functor{.haskell} (without using undefined{.haskell}). #. Is this statement true or false?

> The composition of two `Functor`{.haskell}s is also a `Functor`{.haskell}.

If false, give a counterexample; if true, prove it by exhibiting some appropriate Haskell code.

Laws

As far as the Haskell language itself is concerned, the only requirement to be a Functor{.haskell} is an implementation of fmap{.haskell} with the proper type. Any sensible Functor{.haskell} instance, however, will also satisfy the functor laws, which are part of the definition of a mathematical functor. There are two:

fmap id = id
fmap (g . h) = (fmap g) . (fmap h)

Together, these laws ensure that fmap g{.haskell} does not change the structure of a container, only the elements. Equivalently, and more simply, they ensure that fmap g{.haskell} changes a value without altering its context ^[Technically, these laws make f and fmap{.haskell} together an endofunctor on Hask, the category of Haskell types (ignoring $\bot$, which is a party pooper). See Wikibook: Category theory.].

The first law says that mapping the identity function over every item in a container has no effect. The second says that mapping a composition of two functions over every item in a container is the same as first mapping one function, and then mapping the other.

As an example, the following code is a “valid” instance of Functor{.haskell} (it typechecks), but it violates the functor laws. Do you see why?

-- Evil Functor instance
instance Functor [] where
  fmap _ [] = []
  fmap g (x:xs) = g x : g x : fmap g xs

Any Haskeller worth their salt would reject this code as a gruesome abomination.

Unlike some other type classes we will encounter, a given type has at most one valid instance of Functor{.haskell}. This can be proven via the free theorem for the type of fmap{.haskell}. In fact, GHC can automatically derive Functor{.haskell} instances for many data types.

A similar argument also shows that any Functor{.haskell} instance satisfying the first law (fmap id = id{.haskell}) will automatically satisfy the second law as well. Practically, this means that only the first law needs to be checked (usually by a very straightforward induction) to ensure that a Functor{.haskell} instance is valid.^[Actually, if seq{.haskell}/undefined{.haskell} are considered, it is possible to have an implementation which satisfies the first law but not the second. The rest of the comments in this section should considered in a context where seq{.haskell} and undefined{.haskell} are excluded.]

Exercises

#. Although it is not possible for a Functor{.haskell} instance to satisfy the first Functor{.haskell} law but not the second (excluding undefined{.haskell}), the reverse is possible. Give an example of a (bogus) Functor{.haskell} instance which satisfies the second law but not the first. #. Which laws are violated by the evil Functor{.haskell} instance for list shown above: both laws, or the first law alone? Give specific counterexamples.

Intuition

There are two fundamental ways to think about fmap{.haskell}. The first has already been mentioned: it takes two parameters, a function and a container, and applies the function “inside” the container, producing a new container. Alternately, we can think of fmap{.haskell} as applying a function to a value in a context (without altering the context).

Just like all other Haskell functions of “more than one parameter”, however, fmap{.haskell} is actually curried: it does not really take two parameters, but takes a single parameter and returns a function. For emphasis, we can write fmap{.haskell}’s type with extra parentheses: fmap :: (a -> b) -> (f a -> f b){.haskell}. Written in this form, it is apparent that fmap{.haskell} transforms a “normal” function (g :: a -> b{.haskell}) into one which operates over containers/contexts (fmap g :: f a -> f b{.haskell}). This transformation is often referred to as a lift; fmap{.haskell} “lifts” a function from the “normal world” into the “f world”.

Further reading

A good starting point for reading about the category theory behind the concept of a functor is the excellent Haskell wikibook page on category theory.

Applicative

A somewhat newer addition to the pantheon of standard Haskell type classes, applicative functors represent an abstraction lying in between Functor{.haskell} and Monad{.haskell} in expressivity, first described by McBride and Paterson. The title of their classic paper, Applicative Programming with Effects, gives a hint at the intended intuition behind the Applicative{.haskell} type class. It encapsulates certain sorts of “effectful” computations in a functionally pure way, and encourages an “applicative” programming style. Exactly what these things mean will be seen later.

Definition

Recall that Functor{.haskell} allows us to lift a “normal” function to a function on computational contexts. But fmap{.haskell} doesn’t allow us to apply a function which is itself in a context to a value in a context. Applicative{.haskell} gives us just such a tool, (<*>){.haskell}. It also provides a method, pure{.haskell}, for embedding values in a default, “effect free” context. Here is the type class declaration for Applicative{.haskell}, as defined in Control.Applicative:

class Functor f => Applicative f where
  pure  :: a -> f a
  (<*>) :: f (a -> b) -> f a -> f b

Note that every Applicative{.haskell} must also be a Functor{.haskell}. In fact, as we will see, fmap{.haskell} can be implemented using the Applicative{.haskell} methods, so every Applicative{.haskell} is a functor whether we like it or not; the Functor{.haskell} constraint forces us to be honest.

As always, it’s crucial to understand the type signatures. First, consider (<*>): the best way of thinking about it comes from noting that the type of (<*>){.haskell} is similar to the type of ($){.haskell} ^[Recall that ($) is just function application: f $ x = f x.], but with everything enclosed in an f. In other words, (<*>){.haskell} is just function application within a computational context. The type of (<*>){.haskell} is also very similar to the type of fmap{.haskell}; the only difference is that the first parameter is f (a -> b){.haskell}, a function in a context, instead of a “normal” function (a -> b){.haskell}.

pure{.haskell} takes a value of any type a, and returns a context/container of type f a{.haskell}. The intention is that pure{.haskell} creates some sort of “default” container or “effect free” context. In fact, the behavior of pure{.haskell} is quite constrained by the laws it should satisfy in conjunction with (<*>){.haskell}. Usually, for a given implementation of (<*>){.haskell} there is only one possible implementation of pure{.haskell}.

(Note that previous versions of the Typeclassopedia explained pure{.haskell} in terms of a type class Pointed{.haskell}, which can still be found in the pointed package. However, the current consensus is that Pointed{.haskell} is not very useful after all. For a more detailed explanation, see [Why not Pointed?](http://www.haskell.org/haskellwiki/Why not Pointed%3F))

Laws

Traditionally, there are four laws that Applicative{.haskell} instances should satisfy ^[See haddock for Applicative and Applicative programming with effects]. In some sense, they are all concerned with making sure that pure{.haskell} deserves its name:

Considered as left-to-right rewrite rules, the homomorphism, interchange, and composition laws actually constitute an algorithm for transforming any expression using pure{.haskell} and (<*>){.haskell} into a canonical form with only a single use of pure{.haskell} at the very beginning and only left-nested occurrences of (<*>){.haskell}. Composition allows reassociating (<*>); interchange allows moving occurrences of pure{.haskell} leftwards; and homomorphism allows collapsing multiple adjacent occurrences of pure{.haskell} into one.

There is also a law specifying how Applicative{.haskell} should relate to Functor{.haskell}:

fmap g x = pure g <*> x

It says that mapping a pure function g over a context x is the same as first injecting g into a context with pure{.haskell}, and then applying it to x with (<*>){.haskell}. In other words, we can decompose fmap{.haskell} into two more atomic operations: injection into a context, and application within a context. The Control.Applicative module also defines (<$>){.haskell} as a synonym for fmap{.haskell}, so the above law can also be expressed as:

g <$> x = pure g <*> x{.haskell}.

Exercises

#. (Tricky) One might imagine a variant of the interchange law that says something about applying a pure function to an effectful argument. Using the above laws, prove that pure f <*> x = pure (flip ($)) <*> x <*> pure f{.haskell}

Instances

Most of the standard types which are instances of Functor{.haskell} are also instances of Applicative{.haskell}.

Maybe{.haskell} can easily be made an instance of Applicative{.haskell}; writing such an instance is left as an exercise for the reader.

The list type constructor []{.haskell} can actually be made an instance of Applicative{.haskell} in two ways; essentially, it comes down to whether we want to think of lists as ordered collections of elements, or as contexts representing multiple results of a nondeterministic computation (see Wadler’s How to replace failure by a list of successes).

Let’s first consider the collection point of view. Since there can only be one instance of a given type class for any particular type, one or both of the list instances of Applicative{.haskell} need to be defined for a newtype{.haskell} wrapper; as it happens, the nondeterministic computation instance is the default, and the collection instance is defined in terms of a newtype{.haskell} called ZipList{.haskell}. This instance is:

newtype ZipList a = ZipList { getZipList :: [a] }

instance Applicative ZipList where
  pure = undefined   -- exercise
  (ZipList gs) <*> (ZipList xs) = ZipList (zipWith ($) gs xs)

To apply a list of functions to a list of inputs with (<*>){.haskell}, we just match up the functions and inputs elementwise, and produce a list of the resulting outputs. In other words, we “zip” the lists together with function application, ($); hence the name ZipList{.haskell}.

The other Applicative{.haskell} instance for lists, based on the nondeterministic computation point of view, is:

instance Applicative [] where
  pure x    = [x]
  gs <*> xs = [ g x | g <- gs, x <- xs ]

Instead of applying functions to inputs pairwise, we apply each function to all the inputs in turn, and collect all the results in a list.

Now we can write nondeterministic computations in a natural style. To add the numbers 3 and 4 deterministically, we can of course write (+) 3 4{.haskell}. But suppose instead of 3 we have a nondeterministic computation that might result in 2, 3, or 4; then we can write

  pure (+) <*> [2,3,4] <*> pure 4

or, more idiomatically,

  (+) <$> [2,3,4] <*> pure 4.

There are several other Applicative{.haskell} instances as well:

Exercises

#. Implement an instance of Applicative{.haskell} for Maybe{.haskell}. #. Determine the correct definition of pure{.haskell} for the ZipList{.haskell} instance of Applicative{.haskell}—there is only one implementation that satisfies the law relating pure{.haskell} and (<*>){.haskell}.

Intuition

McBride and Paterson’s paper introduces the notation $[[g ; x_1 ; x_2 ; \cdots ; x_n]]$ to denote function application in a computational context. If each $x_i\ $ has type $f ; t_i\ $ for some applicative functor $f\ $, and $g\ $ has type $t_1 \to t_2 \to \dots \to t_n \to t\ $, then the entire expression $[[g ; x_1 ; \cdots ; x_n]]$ has type $f ; t\ $. You can think of this as applying a function to multiple “effectful” arguments. In this sense, the double bracket notation is a generalization of fmap{.haskell}, which allows us to apply a function to a single argument in a context.

Why do we need Applicative{.haskell} to implement this generalization of fmap{.haskell}? Suppose we use fmap{.haskell} to apply g to the first parameter x1{.haskell}. Then we get something of type f (t2 -> ... t){.haskell}, but now we are stuck: we can’t apply this function-in-a-context to the next argument with fmap{.haskell}. However, this is precisely what (<*>){.haskell} allows us to do.

This suggests the proper translation of the idealized notation $[[g ; x_1 ; x_2 ; \cdots ; x_n]]$ into Haskell, namely

  g <$> x1 <*> x2 <*> ... <*> xn,

recalling that Control.Applicative defines (<$>){.haskell} as convenient infix shorthand for fmap{.haskell}. This is what is meant by an “applicative style”—effectful computations can still be described in terms of function application; the only difference is that we have to use the special operator (<*>){.haskell} for application instead of simple juxtaposition.

Note that pure{.haskell} allows embedding “non-effectful” arguments in the middle of an idiomatic application, like

  g <$> x1 <*> pure x2 <*> x3

which has type f d{.haskell}, given

g  :: a -> b -> c -> d
x1 :: f a
x2 :: b
x3 :: f c

The double brackets are commonly known as “idiom brackets”, because they allow writing “idiomatic” function application, that is, function application that looks normal but has some special, non-standard meaning (determined by the particular instance of Applicative{.haskell} being used). Idiom brackets are not supported by GHC, but they are supported by the Strathclyde Haskell Enhancement, a preprocessor which (among many other things) translates idiom brackets into standard uses of (<$>){.haskell} and (<*>){.haskell}. This can result in much more readable code when making heavy use of Applicative{.haskell}.

Alternative formulation

An alternative, equivalent formulation of Applicative{.haskell} is given by

class Functor f => Monoidal f where
  unit :: f ()
  (**) :: f a -> f b -> f (a,b)

Intuitively, this states that a monoidal functor^[In category-theory speak, we say f is a lax monoidal functor because there aren’t necessarily functions in the other direction, like f (a, b) -> (f a, f b){.haskell}.] is one which has some sort of “default shape” and which supports some sort of “combining” operation. pure{.haskell} and (<*>){.haskell} are equivalent in power to unit{.haskell} and (**){.haskell} (see the Exercises below).

More technically, the idea is that f preserves the “monoidal structure” given by the pairing constructor (,){.haskell} and unit type (){.haskell}. This can be seen even more clearly if we rewrite the types of unit{.haskell} and (**){.haskell} as

unit' :: () -> f ()
(**') :: (f a, f b) -> f (a, b)

Furthermore, to deserve the name “monoidal” (see the section on Monoids), instances of Monoidal{.haskell} ought to satisfy the following laws, which seem much more straightforward than the traditional Applicative{.haskell} laws:

These turn out to be equivalent to the usual Applicative{.haskell} laws. In a category theory setting, one would also require a naturality law:

but in the context of Haskell, this is a free theorem.

Much of this section was taken from a blog post by Edward Z. Yang; see his actual post for a bit more information.

Exercises

#. Implement pure{.haskell} and (<*>){.haskell} in terms of unit{.haskell} and (**){.haskell}, and vice versa. #. Are there any Applicative{.haskell} instances for which there are also functions f () -> (){.haskell} and f (a,b) -> (f a, f b){.haskell}, satisfying some “reasonable” laws? #. (Tricky) Prove that given your implementations from the previous exercise, the usual Applicative{.haskell} laws and the Monoidal{.haskell} laws stated above are equivalent.

Further reading

There are many other useful combinators in the standard libraries implemented in terms of pure{.haskell} and (<*>): for example, (*>){.haskell}, (<*){.haskell}, (<**>){.haskell}, (<$){.haskell}, and so on (see haddock for Applicative). Judicious use of such secondary combinators can often make code using Applicative{.haskell}s much easier to read.

McBride and Paterson’s original paper is a treasure-trove of information and examples, as well as some perspectives on the connection between Applicative{.haskell} and category theory. Beginners will find it difficult to make it through the entire paper, but it is extremely well-motivated—even beginners will be able to glean something from reading as far as they are able.

Conal Elliott has been one of the biggest proponents of Applicative{.haskell}. For example, the Pan library for functional images and the reactive library for functional reactive programming (FRP) ^[Introduced by an earlier paper that was since superseded by Push-pull functional reactive programming.] make key use of it; his blog also contains many examples of Applicative{.haskell} in action. Building on the work of McBride and Paterson, Elliott also built the TypeCompose library, which embodies the observation (among others) that Applicative{.haskell} types are closed under composition; therefore, Applicative{.haskell} instances can often be automatically derived for complex types built out of simpler ones.

Although the Parsec parsing library (paper) was originally designed for use as a monad, in its most common use cases an Applicative{.haskell} instance can be used to great effect; Bryan O’Sullivan’s blog post is a good starting point. If the extra power provided by Monad{.haskell} isn’t needed, it’s usually a good idea to use Applicative{.haskell} instead.

A couple other nice examples of Applicative{.haskell} in action include the ConfigFile and HSQL libraries and the formlets library.

Gershom Bazerman’s post contains many insights into applicatives.

Monad

It’s a safe bet that if you’re reading this, you’ve heard of monads—although it’s quite possible you’ve never heard of Applicative{.haskell} before, or Arrow{.haskell}, or even Monoid{.haskell}. Why are monads such a big deal in Haskell? There are several reasons.

I will let you judge for yourself whether these are good reasons.

In the end, despite all the hoopla, Monad{.haskell} is just another type class. Let’s take a look at its definition.

Definition

The type class declaration for Monad{.haskell} is:

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

  fail   :: String -> m a

The Monad{.haskell} type class is exported by the Prelude{.haskell}, along with a few standard instances. However, many utility functions are found in Control.Monad, and there are also several instances (such as ((->) e){.haskell}) defined in Control.Monad.Instances.

Let’s examine the methods in the Monad{.haskell} class one by one. The type of return{.haskell} should look familiar; it’s the same as pure{.haskell}. Indeed, return{.haskell} is pure{.haskell}, but with an unfortunate name. (Unfortunate, since someone coming from an imperative programming background might think that return{.haskell} is like the C or Java keyword of the same name, when in fact the similarities are minimal.) From a mathematical point of view, every monad is an applicative functor, but for historical reasons, the Monad{.haskell} type class declaration unfortunately does not require this. ^[However, as of GHC 7.10 this will be fixed!]

We can see that (>>){.haskell} is a specialized version of (>>=){.haskell}, with a default implementation given. It is only included in the type class declaration so that specific instances of Monad{.haskell} can override the default implementation of (>>){.haskell} with a more efficient one, if desired. Also, note that although _ >> n = n{.haskell} would be a type-correct implementation of (>>){.haskell}, it would not correspond to the intended semantics: the intention is that m >> n{.haskell} ignores the result of m, but not its effects.

The fail{.haskell} function is an awful hack that has no place in the Monad{.haskell} class; more on this later.

The only really interesting thing to look at—and what makes Monad{.haskell} strictly more powerful than Applicative{.haskell}—is (>>=){.haskell}, which is often called bind. An alternative definition of Monad{.haskell} could look like:

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

We could spend a while talking about the intuition behind (>>=)—and we will. But first, let’s look at some examples.

Instances

Even if you don’t understand the intuition behind the Monad{.haskell} class, you can still create instances of it by just seeing where the types lead you. You may be surprised to find that this actually gets you a long way towards understanding the intuition; at the very least, it will give you some concrete examples to play with as you read more about the Monad{.haskell} class in general. The first few examples are from the standard Prelude{.haskell}; the remaining examples are from the transformers package.

Exercises

#. Implement a Monad{.haskell} instance for the list constructor, []{.haskell}. Follow the types! #. Implement a Monad{.haskell} instance for ((->) e){.haskell}. #. Implement Functor{.haskell} and Monad{.haskell} instances for Free f{.haskell}, defined as

```haskell
data Free f a = Var a
              | Node (f (Free f a))
```

You may assume that `f` has a `Functor`{.haskell} instance.  This is known as the *free monad* built from the functor `f`.

Intuition

Let’s look more closely at the type of (>>=){.haskell}. The basic intuition is that it combines two computations into one larger computation. The first argument, m a{.haskell}, is the first computation. However, it would be boring if the second argument were just an m b{.haskell}; then there would be no way for the computations to interact with one another (actually, this is exactly the situation with Applicative{.haskell}). So, the second argument to (>>=){.haskell} has type a -> m b{.haskell}: a function of this type, given a result of the first computation, can produce a second computation to be run. In other words, x >>= k{.haskell} is a computation which runs x, and then uses the result(s) of x to decide what computation to run second, using the output of the second computation as the result of the entire computation.

Intuitively, it is this ability to use the output from previous computations to decide what computations to run next that makes Monad{.haskell} more powerful than Applicative{.haskell}. The structure of an Applicative{.haskell} computation is fixed, whereas the structure of a Monad{.haskell} computation can change based on intermediate results. This also means that parsers built using an Applicative{.haskell} interface can only parse context-free languages; in order to parse context-sensitive languages a Monad{.haskell} interface is needed.^[Actually, because Haskell allows general recursion, this is a lie: using a Haskell parsing library one can recursively construct infinite grammars, and hence Applicative{.haskell} (together with Alternative{.haskell}) is enough to parse any context-sensitive language with a finite alphabet. See Parsing context-sensitive languages with Applicative.]

To see the increased power of Monad{.haskell} from a different point of view, let’s see what happens if we try to implement (>>=){.haskell} in terms of fmap{.haskell}, pure{.haskell}, and (<*>){.haskell}. We are given a value x of type m a{.haskell}, and a function k of type a -> m b{.haskell}, so the only thing we can do is apply k to x. We can’t apply it directly, of course; we have to use fmap{.haskell} to lift it over the m. But what is the type of fmap k{.haskell}? Well, it’s m a -> m (m b){.haskell}. So after we apply it to x, we are left with something of type m (m b)—but now we are stuck; what we really want is an m b{.haskell}, but there’s no way to get there from here. We can add m’s using pure{.haskell}, but we have no way to collapse multiple m’s into one.

This ability to collapse multiple m’s is exactly the ability provided by the function join :: m (m a) -> m a{.haskell}, and it should come as no surprise that an alternative definition of Monad{.haskell} can be given in terms of join{.haskell}:

class Applicative m => Monad'' m where
  join :: m (m a) -> m a

In fact, the canonical definition of monads in category theory is in terms of return{.haskell}, fmap{.haskell}, and join{.haskell} (often called $\eta$, $T$, and $\mu$ in the mathematical literature). Haskell uses an alternative formulation with (>>=){.haskell} instead of join{.haskell} since it is more convenient to use ^[You might hear some people claim that that the definition in terms of return{.haskell}, fmap{.haskell}, and join{.haskell} is the “math definition” and the definition in terms of return{.haskell} and (>>=){.haskell} is something specific to Haskell. In fact, both definitions were known in the mathematics community long before Haskell picked up monads.]. However, sometimes it can be easier to think about Monad{.haskell} instances in terms of join{.haskell}, since it is a more “atomic” operation. (For example, join{.haskell} for the list monad is just concat{.haskell}.)

Exercises

#. Implement (>>=){.haskell} in terms of fmap{.haskell} (or liftM{.haskell}) and join{.haskell}. #. Now implement join{.haskell} and fmap{.haskell} (liftM{.haskell}) in terms of (>>=){.haskell} and return{.haskell}.

Utility functions

The Control.Monad module provides a large number of convenient utility functions, all of which can be implemented in terms of the basic Monad{.haskell} operations (return{.haskell} and (>>=){.haskell} in particular). We have already seen one of them, namely, join{.haskell}. We also mention some other noteworthy ones here; implementing these utility functions oneself is a good exercise. For a more detailed guide to these functions, with commentary and example code, see Henk-Jan van Tuyl’s tour.

Many of these functions also have “underscored” variants, such as sequence_{.haskell} and mapM_{.haskell}; these variants throw away the results of the computations passed to them as arguments, using them only for their side effects.

Other monadic functions which are occasionally useful include filterM{.haskell}, zipWithM{.haskell}, foldM{.haskell}, and forever{.haskell}.

Laws

There are several laws that instances of Monad{.haskell} should satisfy (see also the [Monad laws](http://www.haskell.org/haskellwiki/Monad laws) wiki page). The standard presentation is:

return a >>= k  =  k a
m >>= return    =  m
m >>= (\x -> k x >>= h)  =  (m >>= k) >>= h

fmap f xs  =  xs >>= return . f  =  liftM f xs

The first and second laws express the fact that return{.haskell} behaves nicely: if we inject a value a into a monadic context with return{.haskell}, and then bind to k, it is the same as just applying k to a in the first place; if we bind a computation m to return{.haskell}, nothing changes. The third law essentially says that (>>=){.haskell} is associative, sort of. The last law ensures that fmap{.haskell} and liftM{.haskell} are the same for types which are instances of both Functor{.haskell} and Monad{.haskell}—which, as already noted, should be every instance of Monad{.haskell}.

However, the presentation of the above laws, especially the third, is marred by the asymmetry of (>>=){.haskell}. It’s hard to look at the laws and see what they’re really saying. I prefer a much more elegant version of the laws, which is formulated in terms of (>=>){.haskell} ^[I like to pronounce this operator “fish”.]. Recall that (>=>){.haskell} “composes” two functions of type a -> m b{.haskell} and b -> m c{.haskell}. You can think of something of type a -> m b{.haskell} (roughly) as a function from a to b which may also have some sort of effect in the context corresponding to m. (>=>){.haskell} lets us compose these “effectful functions”, and we would like to know what properties (>=>){.haskell} has. The monad laws reformulated in terms of (>=>){.haskell} are:

return >=> g  =  g
g >=> return  =  g
(g >=> h) >=> k  =  g >=> (h >=> k)

Ah, much better! The laws simply state that return{.haskell} is the identity of (>=>){.haskell}, and that (>=>){.haskell} is associative ^[As fans of category theory will note, these laws say precisely that functions of type a -> m b{.haskell} are the arrows of a category with (>=>){.haskell} as composition! Indeed, this is known as the Kleisli category of the monad m. It will come up again when we discuss Arrow{.haskell}s.].

There is also a formulation of the monad laws in terms of fmap{.haskell}, return{.haskell}, and join{.haskell}; for a discussion of this formulation, see the Haskell wikibook page on category theory.

Exercises

#. Given the definition g >=> h = \x -> g x >>= h{.haskell}, prove the equivalence of the above laws and the usual monad laws.

do notation

Haskell’s special do notation supports an “imperative style” of programming by providing syntactic sugar for chains of monadic expressions. The genesis of the notation lies in realizing that something like a >>= \x -> b >> c >>= \y -> d{.haskell} can be more readably written by putting successive computations on separate lines:

a >>= \x ->
b >>
c >>= \y ->
d

This emphasizes that the overall computation consists of four computations a, b, c, and d, and that x is bound to the result of a, and y is bound to the result of c (b, c, and d are allowed to refer to x, and d is allowed to refer to y as well). From here it is not hard to imagine a nicer notation:

do { x <- a
   ;      b
   ; y <- c
   ;      d
   }

(The curly braces and semicolons may optionally be omitted; the Haskell parser uses layout to determine where they should be inserted.) This discussion should make clear that do notation is just syntactic sugar. In fact, do blocks are recursively translated into monad operations (almost) like this:

                  do e → e
       do { e; stmts } → e >> do { stmts }
  do { v <- e; stmts } → e >>= \v -> do { stmts }
do { let decls; stmts} → let decls in do { stmts }

This is not quite the whole story, since v might be a pattern instead of a variable. For example, one can write

do (x:xs) <- foo
   bar x

but what happens if foo{.haskell} produces an empty list? Well, remember that ugly fail{.haskell} function in the Monad{.haskell} type class declaration? That’s what happens. See section 3.14 of the Haskell Report for the full details. See also the discussion of MonadPlus{.haskell} and MonadZero{.haskell} in the section on other monoidal classes.

A final note on intuition: do notation plays very strongly to the “computational context” point of view rather than the “container” point of view, since the binding notation x <- m{.haskell} is suggestive of “extracting” a single x from m and doing something with it. But m may represent some sort of a container, such as a list or a tree; the meaning of x <- m{.haskell} is entirely dependent on the implementation of (>>=){.haskell}. For example, if m is a list, x <- m{.haskell} actually means that x will take on each value from the list in turn.

Further reading

Philip Wadler was the first to propose using monads to structure functional programs. His paper is still a readable introduction to the subject.

There are, of course, numerous monad tutorials of varying quality ^[[All About Monads](http://www.haskell.org/haskellwiki/All About Monads), Monads as containers, Understanding monads, [The Monadic Way](http://www.haskell.org/haskellwiki/The Monadic Way), You Could Have Invented Monads! (And Maybe You Already Have.), there’s a monster in my Haskell!, Understanding Monads. For real., Monads in 15 minutes: Backtracking and Maybe, Monads as computation, Practical Monads].

A few of the best include Cale Gibbard’s Monads as containers and Monads as computation; Jeff Newbern’s [All About Monads](http://www.haskell.org/haskellwiki/All About Monads), a comprehensive guide with lots of examples; and Dan Piponi’s You Could Have Invented Monads!, which features great exercises. If you just want to know how to use IO{.haskell}, you could consult the [Introduction to IO](http://www.haskell.org/haskellwiki/Introduction to IO). Even this is just a sampling; the [monad tutorials timeline](http://www.haskell.org/haskellwiki/monad tutorials timeline) is a more complete list. (All these monad tutorials have prompted parodies like think of a monad … as well as other kinds of backlash like Monads! (and Why Monad Tutorials Are All Awful) or Abstraction, intuition, and the “monad tutorial fallacy”.)

Other good monad references which are not necessarily tutorials include Henk-Jan van Tuyl’s tour of the functions in Control.Monad, Dan Piponi’s field guide, Tim Newsham’s What’s a Monad?, and Chris Smith’s excellent article Why Do Monads Matter?. There are also many blog posts which have been written on various aspects of monads; a collection of links can be found on the Haskell Wiki under [Blog articles/Monads](http://www.haskell.org/haskellwiki/Blog articles/Monads).

For help constructing monads from scratch, and for obtaining a “deep embedding” of monad operations suitable for use in, say, compiling a domain-specific language, see Apfelmus’s operational package.

One of the quirks of the Monad{.haskell} class and the Haskell type system is that it is not possible to straightforwardly declare Monad{.haskell} instances for types which require a class constraint on their data, even if they are monads from a mathematical point of view. For example, Data.Set requires an Ord{.haskell} constraint on its data, so it cannot be easily made an instance of Monad{.haskell}. A solution to this problem was first described by Eric Kidd, and later made into a library named rmonad by Ganesh Sittampalam and Peter Gavin.

There are many good reasons for eschewing do notation; some have gone so far as to consider it harmful.

Monads can be generalized in various ways; for an exposition of one possibility, see Robert Atkey’s paper on parameterized monads, or Dan Piponi’s Beyond Monads.

For the categorically inclined, monads can be viewed as monoids (From Monoids to Monads) and also as closure operators Triples and Closure. Derek Elkins’s article in issue 13 of the Monad.Reader contains an exposition of the category-theoretic underpinnings of some of the standard Monad{.haskell} instances, such as State{.haskell} and Cont{.haskell}. Jonathan Hill and Keith Clarke have an early paper explaining the connection between monads as they arise in category theory and as used in functional programming. There is also a web page by Oleg Kiselyov explaining the history of the IO monad.

Links to many more research papers related to monads can be found on the Haskell Wiki under [Research papers/Monads and arrows](http://www.haskell.org/haskellwiki/Research papers/Monads and arrows).

Monad transformers

One would often like to be able to combine two monads into one: for example, to have stateful, nondeterministic computations (State{.haskell} + []{.haskell}), or computations which may fail and can consult a read-only environment (Maybe{.haskell} + Reader{.haskell}), and so on. Unfortunately, monads do not compose as nicely as applicative functors (yet another reason to use Applicative{.haskell} if you don’t need the full power that Monad{.haskell} provides), but some monads can be combined in certain ways.

Standard monad transformers

The transformers library provides a number of standard monad transformers. Each monad transformer adds a particular capability/feature/effect to any existing monad.

For example, StateT s Maybe{.haskell} is an instance of Monad{.haskell}; computations of type StateT s Maybe a{.haskell} may fail, and have access to a mutable state of type s. Monad transformers can be multiply stacked. One thing to keep in mind while using monad transformers is that the order of composition matters. For example, when a StateT s Maybe a{.haskell} computation fails, the state ceases being updated (indeed, it simply disappears); on the other hand, the state of a MaybeT (State s) a{.haskell} computation may continue to be modified even after the computation has “failed”. This may seem backwards, but it is correct. Monad transformers build composite monads “inside out”; MaybeT (State s) a{.haskell} is isomorphic to s -> (Maybe a, s){.haskell}. (Lambdabot has an indispensable @unmtl command which you can use to “unpack” a monad transformer stack in this way.) Intuitively, the monads become “more fundamental” the further inside the stack you get, and the effects of inner monads “have precedence” over the effects of outer ones. Of course, this is just handwaving, and if you are unsure of the proper order for some monads you wish to combine, there is no substitute for using @unmtl or simply trying out the various options.

Definition and laws

All monad transformers should implement the MonadTrans{.haskell} type class, defined in Control.Monad.Trans.Class:

class MonadTrans t where
  lift :: Monad m => m a -> t m a

It allows arbitrary computations in the base monad m to be “lifted” into computations in the transformed monad t m{.haskell}. (Note that type application associates to the left, just like function application, so t m a = (t m) a{.haskell}.)

lift{.haskell} must satisfy the laws

lift . return   =  return
lift (m >>= f)  =  lift m >>= (lift . f)

which intuitively state that lift{.haskell} transforms m a{.haskell} computations into t m a{.haskell} computations in a “sensible” way, which sends the return{.haskell} and (>>=){.haskell} of m to the return{.haskell} and (>>=){.haskell} of t m{.haskell}.

Exercises

#. What is the kind of t in the declaration of MonadTrans{.haskell}?

Transformer type classes and “capability” style

There are also type classes (provided by the mtl package) for the operations of each transformer. For example, the MonadState{.haskell} type class provides the state-specific methods get{.haskell} and put{.haskell}, allowing you to conveniently use these methods not only with State{.haskell}, but with any monad which is an instance of MonadState{.haskell}—including MaybeT (State s){.haskell}, StateT s (ReaderT r IO){.haskell}, and so on. Similar type classes exist for Reader{.haskell}, Writer{.haskell}, Cont{.haskell}, IO{.haskell}, and others ^[The only problem with this scheme is the quadratic number of instances required as the number of standard monad transformers grows—but as the current set of standard monad transformers seems adequate for most common use cases, this may not be that big of a deal.].

These type classes serve two purposes. First, they get rid of (most of) the need for explicitly using lift{.haskell}, giving a type-directed way to automatically determine the right number of calls to lift{.haskell}. Simply writing put{.haskell} will be automatically translated into lift . put{.haskell}, lift . lift . put{.haskell}, or something similar depending on what concrete monad stack you are using.

Second, they give you more flexibility to switch between different concrete monad stacks. For example, if you are writing a state-based algorithm, don’t write

foo :: State Int Char
foo = modify (*2) >> return 'x'

but rather

foo :: MonadState Int m => m Char
foo = modify (*2) >> return 'x'

Now, if somewhere down the line you realize you need to introduce the possibility of failure, you might switch from State Int{.haskell} to MaybeT (State Int){.haskell}. The type of the first version of foo{.haskell} would need to be modified to reflect this change, but the second version of foo{.haskell} can still be used as-is.

However, this sort of “capability-based” style (e.g. specifying that foo{.haskell} works for any monad with the “state capability”) quickly runs into problems when you try to naively scale it up: for example, what if you need to maintain two independent states? A framework for solving this and related problems is described by Schrijvers and Olivera (Monads, zippers and views: virtualizing the monad stack, ICFP 2011) and is implemented in the Monatron package.

Composing monads

Is the composition of two monads always a monad? As hinted previously, the answer is no.

Since Applicative{.haskell} functors are closed under composition, the problem must lie with join{.haskell}. Indeed, suppose m and n are arbitrary monads; to make a monad out of their composition we would need to be able to implement

join :: m (n (m (n a))) -> m (n a)

but it is not clear how this could be done in general. The join{.haskell} method for m is no help, because the two occurrences of m are not next to each other (and likewise for n).

However, one situation in which it can be done is if n distributes over m, that is, if there is a function

distrib :: n (m a) -> m (n a)

satisfying certain laws. See Jones and Duponcheel (Composing Monads); see also the section on Traversable.

For a much more in-depth discussion and analysis of the failure of monads to be closed under composition, see this question on StackOverflow.

Exercises

#. Implement join :: M (N (M (N a))) -> M (N a){.haskell}, given distrib :: N (M a) -> M (N a){.haskell} and assuming M and N are instances of Monad{.haskell}.

Further reading

Much of the monad transformer library (originally mtl, now split between mtl and transformers), including the Reader{.haskell}, Writer{.haskell}, State{.haskell}, and other monads, as well as the monad transformer framework itself, was inspired by Mark Jones’s classic paper Functional Programming with Overloading and Higher-Order Polymorphism. It’s still very much worth a read—and highly readable—after almost fifteen years.

See Edward Kmett’s mailing list message for a description of the history and relationships among monad transformer packages (mtl, transformers, monads-fd, monads-tf).

There are two excellent references on monad transformers. Martin Grabmüller’s Monad Transformers Step by Step is a thorough description, with running examples, of how to use monad transformers to elegantly build up computations with various effects. Cale Gibbard’s article on how to use monad transformers is more practical, describing how to structure code using monad transformers to make writing it as painless as possible. Another good starting place for learning about monad transformers is a blog post by Dan Piponi.

The ListT{.haskell} transformer from the transformers package comes with the caveat that ListT m{.haskell} is only a monad when m is commutative, that is, when ma >>= \a -> mb >>= \b -> foo{.haskell} is equivalent to mb >>= \b -> ma >>= \a -> foo{.haskell} (i.e. the order of m‘s effects does not matter). For one explanation why, see Dan Piponi’s blog post “Why isn’t ListT []{.haskell} a monad”. For more examples, as well as a design for a version of ListT{.haskell} which does not have this problem, see ListT{.haskell} done right.

There is an alternative way to compose monads, using coproducts, as described by Lüth and Ghani. This method is interesting but has not (yet?) seen widespread use. For a more recent alternative, see Kiselyov et al’s Extensible Effects: An Alternative to Monad Transformers.

MonadFix

Note: MonadFix{.haskell} is included here for completeness (and because it is interesting) but seems not to be used much. Skipping this section on a first read-through is perfectly OK (and perhaps even recommended).

mdo/do rec notation

The MonadFix{.haskell} class describes monads which support the special fixpoint operation mfix :: (a -> m a) -> m a{.haskell}, which allows the output of monadic computations to be defined via (effectful) recursion. This is supported in GHC by a special “recursive do” notation, enabled by the -XDoRec flag^[In GHC 7.6, the flag has been changed to -XRecursiveDo.]. Within a do block, one may have a nested rec block, like so:

do { x <- foo
   ; rec { y <- baz
         ; z <- bar
         ;      bob
         }
   ; w <- frob
   }

Normally (if we had do in place of rec in the above example), y would be in scope in bar{.haskell} and bob{.haskell} but not in baz{.haskell}, and z would be in scope only in bob{.haskell}. With the rec{.haskell}, however, y and z are both in scope in all three of baz{.haskell}, bar{.haskell}, and bob{.haskell}. A rec{.haskell} block is analogous to a let{.haskell} block such as

let { y = baz
    ; z = bar
    }
in bob

because, in Haskell, every variable bound in a let{.haskell}-block is in scope throughout the entire block. (From this point of view, Haskell’s normal do blocks are analogous to Scheme’s let* construct.)

What could such a feature be used for? One of the motivating examples given in the original paper describing MonadFix{.haskell} (see below) is encoding circuit descriptions. A line in a do-block such as

  x <- gate y z

describes a gate whose input wires are labeled y and z and whose output wire is labeled x. Many (most?) useful circuits, however, involve some sort of feedback loop, making them impossible to write in a normal do-block (since some wire would have to be mentioned as an input before being listed as an output). Using a rec block solves this problem.

Examples and intuition

Of course, not every monad supports such recursive binding. However, as mentioned above, it suffices to have an implementation of mfix :: (a -> m a) -> m a{.haskell}, satisfying a few laws. Let’s try implementing mfix{.haskell} for the Maybe{.haskell} monad. That is, we want to implement a function

maybeFix :: (a -> Maybe a) -> Maybe a

Let’s think for a moment about the implementation ^[Actually, fix{.haskell} is implemented slightly differently for efficiency reasons; but the given definition is equivalent and simpler for the present purpose.] of the non-monadic fix :: (a -> a) -> a{.haskell}:

fix f = f (fix f)

Inspired by fix{.haskell}, our first attempt at implementing maybeFix{.haskell} might be something like

maybeFix :: (a -> Maybe a) -> Maybe a
maybeFix f = maybeFix f >>= f

This has the right type. However, something seems wrong: there is nothing in particular here about Maybe{.haskell}; maybeFix{.haskell} actually has the more general type Monad m => (a -> m a) -> m a{.haskell}. But didn’t we just say that not all monads support mfix{.haskell}?

The answer is that although this implementation of maybeFix{.haskell} has the right type, it does not have the intended semantics. If we think about how (>>=){.haskell} works for the Maybe{.haskell} monad (by pattern-matching on its first argument to see whether it is Nothing{.haskell} or Just{.haskell}) we can see that this definition of maybeFix{.haskell} is completely useless: it will just recurse infinitely, trying to decide whether it is going to return Nothing{.haskell} or Just{.haskell}, without ever even so much as a glance in the direction of f.

The trick is to simply assume that maybeFix{.haskell} will return Just{.haskell}, and get on with life!

maybeFix :: (a -> Maybe a) -> Maybe a
maybeFix f = ma
  where ma = f (fromJust ma)

This says that the result of maybeFix{.haskell} is ma{.haskell}, and assuming that ma = Just x{.haskell}, it is defined (recursively) to be equal to f x{.haskell}.

Why is this OK? Isn’t fromJust{.haskell} almost as bad as unsafePerformIO{.haskell}? Well, usually, yes. This is just about the only situation in which it is justified! The interesting thing to note is that maybeFix{.haskell} will never crash – although it may, of course, fail to terminate. The only way we could get a crash is if we try to evaluate fromJust ma{.haskell} when we know that ma = Nothing{.haskell}. But how could we know ma = Nothing{.haskell}? Since ma{.haskell} is defined as f (fromJust ma){.haskell}, it must be that this expression has already been evaluated to Nothing{.haskell} – in which case there is no reason for us to be evaluating fromJust ma{.haskell} in the first place!

To see this from another point of view, we can consider three possibilities. First, if f outputs Nothing{.haskell} without looking at its argument, then maybeFix f{.haskell} clearly returns Nothing{.haskell}. Second, if f always outputs Just x{.haskell}, where x depends on its argument, then the recursion can proceed usefully: fromJust ma{.haskell} will be able to evaluate to x, thus feeding f‘s output back to it as input. Third, if f tries to use its argument to decide whether to output Just{.haskell} or Nothing{.haskell}, then maybeFix f{.haskell} will not terminate: evaluating f‘s argument requires evaluating ma{.haskell} to see whether it is Just{.haskell}, which requires evaluating f (fromJust ma){.haskell}, which requires evaluating ma{.haskell}, … and so on.

There are also instances of MonadFix{.haskell} for lists (which works analogously to the instance for Maybe{.haskell}), for ST{.haskell}, and for IO{.haskell}. The instance for IO{.haskell} is particularly amusing: it creates a new (empty) MVar{.haskell}, immediately reads its contents using unsafeInterleaveIO{.haskell} (which delays the actual reading lazily until the value is needed), uses the contents of the MVar{.haskell} to compute a new value, which it then writes back into the MVar{.haskell}. It almost seems, spookily, that mfix{.haskell} is sending a value back in time to itself through the MVar{.haskell} – though of course what is really going on is that the reading is delayed just long enough (via unsafeInterleaveIO{.haskell}) to get the process bootstrapped.

Exercises

#. Implement a MonadFix{.haskell} instance for []{.haskell}.

GHC 7.6 changes

GHC 7.6 reinstated the old mdo syntax, so the example at the start of this section can be written

mdo { x <- foo
    ; y <- baz
    ; z <- bar
    ;      bob
    ; w <- frob
    }

which will be translated into the original example (assuming that, say, bar{.haskell} and bob{.haskell} refer to y. The difference is that mdo{.haskell} will analyze the code in order to find minimal recursive blocks, which will be placed in rec{.haskell} blocks, whereas rec{.haskell} blocks desugar directly into calls to mfix{.haskell} without any further analysis.

Further reading

For more information (such as the precise desugaring rules for rec{.haskell} blocks), see Levent Erkök and John Launchbury’s 2002 Haskell workshop paper, A Recursive do for Haskell, or for full details, Levent Erkök’s thesis, Value Recursion in Monadic Computations. (Note, while reading, that MonadFix{.haskell} used to be called MonadRec{.haskell}.) You can also read the GHC user manual section on recursive do-notation.

Semigroup

A semigroup is a set $S\ $ together with a binary operation $\oplus\ $ which combines elements from $S\ $. The $\oplus\ $ operator is required to be associative (that is, $(a \oplus b) \oplus c = a \oplus (b \oplus c)\ $, for any $a,b,c\ $ which are elements of $S\ $).

For example, the natural numbers under addition form a semigroup: the sum of any two natural numbers is a natural number, and $(a+b)+c = a+(b+c)\ $ for any natural numbers $a\ $, $b\ $, and $c,\ $. The integers under multiplication also form a semigroup, as do the integers (or rationals, or reals) under $\max\ $ or $\min\ $, Boolean values under conjunction and disjunction, lists under concatenation, functions from a set to itself under composition … Semigroups show up all over the place, once you know to look for them.

Definition

Semigroups are not (yet?) defined in the base package, but the semigroups package provides a standard definition.

The definition of the Semigroup{.haskell} type class (haddock) is as follows:

class Semigroup a where
  (<>) :: a -> a -> a

  sconcat :: NonEmpty a -> a
  sconcat = sconcat (a :| as) = go a as where
    go b (c:cs) = b <> go c cs
    go b []     = b

  times1p :: Whole n => n -> a -> a
  times1p = ...

The really important method is (<>){.haskell}, representing the associative binary operation. The other two methods have default implementations in terms of (<>){.haskell}, and are included in the type class in case some instances can give more efficient implementations than the default. sconcat{.haskell} reduces a nonempty list using (<>); times1p n{.haskell} is equivalent to (but more efficient than) sconcat . replicate n{.haskell}. See the haddock documentation for more information on sconcat{.haskell} and times1p{.haskell}.

Laws

The only law is that (<>){.haskell} must be associative:

(x <> y) <> z = x <> (y <> z)

Monoid

Many semigroups have a special element $e$ for which the binary operation $\oplus$ is the identity, that is, $e \oplus x = x \oplus e = x$ for every element $x$. Such a semigroup-with-identity-element is called a monoid.

Definition

The definition of the Monoid{.haskell} type class (defined in Data.Monoid; haddock) is:

class Monoid a where
  mempty  :: a
  mappend :: a -> a -> a

  mconcat :: [a] -> a
  mconcat = foldr mappend mempty

The mempty{.haskell} value specifies the identity element of the monoid, and mappend{.haskell} is the binary operation. The default definition for mconcat{.haskell} “reduces” a list of elements by combining them all with mappend{.haskell}, using a right fold. It is only in the Monoid{.haskell} class so that specific instances have the option of providing an alternative, more efficient implementation; usually, you can safely ignore mconcat{.haskell} when creating a Monoid{.haskell} instance, since its default definition will work just fine.

The Monoid{.haskell} methods are rather unfortunately named; they are inspired by the list instance of Monoid{.haskell}, where indeed mempty = []{.haskell} and mappend = (++){.haskell}, but this is misleading since many monoids have little to do with appending (see these Comments from OCaml Hacker Brian Hurt on the Haskell-cafe mailing list). This was improved in GHC 7.4, where (<>){.haskell} was added as an alias to mappend{.haskell}.

Laws

Of course, every Monoid{.haskell} instance should actually be a monoid in the mathematical sense, which implies these laws:

mempty `mappend` x = x
x `mappend` mempty = x
(x `mappend` y) `mappend` z = x `mappend` (y `mappend` z)

Instances

There are quite a few interesting Monoid{.haskell} instances defined in Data.Monoid.

Monoid{.haskell} is also used to enable several other type class instances. As noted previously, we can use Monoid{.haskell} to make ((,) e){.haskell} an instance of Applicative{.haskell}:

instance Monoid e => Applicative ((,) e) where
  pure x = (mempty, x)
  (u, f) <*> (v, x) = (u `mappend` v, f x)

Monoid{.haskell} can be similarly used to make ((,) e){.haskell} an instance of Monad{.haskell} as well; this is known as the writer monad. As we’ve already seen, Writer{.haskell} and WriterT{.haskell} are a newtype wrapper and transformer for this monad, respectively.

Monoid{.haskell} also plays a key role in the Foldable{.haskell} type class (see section Foldable).

Other monoidal classes: Alternative, MonadPlus, ArrowPlus

The Alternative{.haskell} type class (haddock) is for Applicative{.haskell} functors which also have a monoid structure:

class Applicative f => Alternative f where
  empty :: f a
  (<|>) :: f a -> f a -> f a

Of course, instances of Alternative{.haskell} should satisfy the monoid laws

empty <|> x = x
x <|> empty = x
(x <|> y) <|> z = x <|> (y <|> z)

Likewise, MonadPlus{.haskell} (haddock) is for Monad{.haskell}s with a monoid structure:

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

The MonadPlus{.haskell} documentation states that it is intended to model monads which also support “choice and failure”; in addition to the monoid laws, instances of MonadPlus{.haskell} are expected to satisfy

mzero >>= f  =  mzero
v >> mzero   =  mzero

which explains the sense in which mzero{.haskell} denotes failure. Since mzero{.haskell} should be the identity for mplus{.haskell}, the computation m1 `mplus` m2{.haskell} succeeds (evaluates to something other than mzero{.haskell}) if either m1{.haskell} or m2{.haskell} does; so mplus{.haskell} represents choice. The guard{.haskell} function can also be used with instances of MonadPlus{.haskell}; it requires a condition to be satisfied and fails (using mzero{.haskell}) if it is not. A simple example of a MonadPlus{.haskell} instance is []{.haskell}, which is exactly the same as the Monoid{.haskell} instance for []: the empty list represents failure, and list concatenation represents choice. In general, however, a MonadPlus{.haskell} instance for a type need not be the same as its Monoid{.haskell} instance; Maybe{.haskell} is an example of such a type. A great introduction to the MonadPlus{.haskell} type class, with interesting examples of its use, is Doug Auclair’s MonadPlus: What a Super Monad! in the Monad.Reader issue 11.

There used to be a type class called MonadZero{.haskell} containing only mzero{.haskell}, representing monads with failure. The do-notation requires some notion of failure to deal with failing pattern matches. Unfortunately, MonadZero{.haskell} was scrapped in favor of adding the fail{.haskell} method to the Monad{.haskell} class. If we are lucky, someday MonadZero{.haskell} will be restored, and fail{.haskell} will be banished to the bit bucket where it belongs (see [MonadPlus reform proposal](http://www.haskell.org/haskellwiki/MonadPlus reform proposal)). The idea is that any do-block which uses pattern matching (and hence may fail) would require a MonadZero{.haskell} constraint; otherwise, only a Monad{.haskell} constraint would be required.

Finally, ArrowZero{.haskell} and ArrowPlus{.haskell} (haddock) represent Arrow{.haskell}s (see below) with a monoid structure:

class Arrow arr => ArrowZero arr where
  zeroArrow :: b `arr` c

class ArrowZero arr => ArrowPlus arr where
  (<+>) :: (b `arr` c) -> (b `arr` c) -> (b `arr` c)

Further reading

Monoids have gotten a fair bit of attention recently, ultimately due to a blog post by Brian Hurt, in which he complained about the fact that the names of many Haskell type classes (Monoid{.haskell} in particular) are taken from abstract mathematics. This resulted in a long Haskell-cafe thread arguing the point and discussing monoids in general.

However, this was quickly followed by several blog posts about Monoid{.haskell} ^[May its name live forever.]. First, Dan Piponi wrote a great introductory post, Haskell Monoids and their Uses. This was quickly followed by Heinrich Apfelmus’s Monoids and Finger Trees, an accessible exposition of Hinze and Paterson’s classic paper on 2-3 finger trees, which makes very clever use of Monoid{.haskell} to implement an elegant and generic data structure. Dan Piponi then wrote two fascinating articles about using Monoids (and finger trees): Fast Incremental Regular Expressions and Beyond Regular Expressions

In a similar vein, David Place’s article on improving Data.Map in order to compute incremental folds (see the Monad Reader issue 11) is also a good example of using Monoid{.haskell} to generalize a data structure.

Some other interesting examples of Monoid{.haskell} use include building elegant list sorting combinators, collecting unstructured information, combining probability distributions, and a brilliant series of posts by Chung-Chieh Shan and Dylan Thurston using Monoid{.haskell}s to elegantly solve a difficult combinatorial puzzle (followed by part 2, part 3, part 4).

As unlikely as it sounds, monads can actually be viewed as a sort of monoid, with join{.haskell} playing the role of the binary operation and return{.haskell} the role of the identity; see Dan Piponi’s blog post.

Foldable

The Foldable{.haskell} class, defined in the Data.Foldable module (haddock), abstracts over containers which can be “folded” into a summary value. This allows such folding operations to be written in a container-agnostic way.

Definition

The definition of the Foldable{.haskell} type class is:

class Foldable t where
  fold    :: Monoid m => t m -> m
  foldMap :: Monoid m => (a -> m) -> t a -> m

  foldr   :: (a -> b -> b) -> b -> t a -> b
  foldl   :: (a -> b -> a) -> a -> t b -> a
  foldr1  :: (a -> a -> a) -> t a -> a
  foldl1  :: (a -> a -> a) -> t a -> a

This may look complicated, but in fact, to make a Foldable{.haskell} instance you only need to implement one method: your choice of foldMap{.haskell} or foldr{.haskell}. All the other methods have default implementations in terms of these, and are presumably included in the class in case more efficient implementations can be provided.

Instances and examples

The type of foldMap{.haskell} should make it clear what it is supposed to do: given a way to convert the data in a container into a Monoid{.haskell} (a function a -> m{.haskell}) and a container of a’s (t a{.haskell}), foldMap{.haskell} provides a way to iterate over the entire contents of the container, converting all the a’s to m’s and combining all the m’s with mappend{.haskell}. The following code shows two examples: a simple implementation of foldMap{.haskell} for lists, and a binary tree example provided by the Foldable{.haskell} documentation.

instance Foldable [] where
  foldMap g = mconcat . map g

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

instance Foldable Tree where
  foldMap f Empty        = mempty
  foldMap f (Leaf x)     = f x
  foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r

The foldr{.haskell} function has a type similar to the foldr{.haskell} found in the Prelude{.haskell}, but more general, since the foldr{.haskell} in the Prelude{.haskell} works only on lists.

The Foldable{.haskell} module also provides instances for Maybe{.haskell} and Array{.haskell}; additionally, many of the data structures found in the standard containers library (for example, Map{.haskell}, Set{.haskell}, Tree{.haskell}, and Sequence{.haskell}) provide their own Foldable{.haskell} instances.

Exercises

#. What is the type of foldMap . foldMap{.haskell}? Or foldMap . foldMap . foldMap{.haskell}, etc.? What do they do?

Derived folds

Given an instance of Foldable{.haskell}, we can write generic, container-agnostic functions such as:

-- Compute the size of any container.
containerSize :: Foldable f => f a -> Int
containerSize = getSum . foldMap (const (Sum 1))

-- Compute a list of elements of a container satisfying a predicate.
filterF :: Foldable f => (a -> Bool) -> f a -> [a]
filterF p = foldMap (\a -> if p a then [a] else [])

-- Get a list of all the Strings in a container which include the
-- letter a.
aStrings :: Foldable f => f String -> [String]
aStrings = filterF (elem 'a')

The Foldable{.haskell} module also provides a large number of predefined folds, many of which are generalized versions of Prelude{.haskell} functions of the same name that only work on lists: concat{.haskell}, concatMap{.haskell}, and{.haskell}, or{.haskell}, any{.haskell}, all{.haskell}, sum{.haskell}, product{.haskell}, maximum{.haskell}(By), minimum{.haskell}(By), elem{.haskell}, notElem{.haskell}, and find{.haskell}.

The important function toList{.haskell} is also provided, which turns any Foldable{.haskell} structure into a list of its elements in left-right order; it works by folding with the list monoid.

There are also generic functions that work with Applicative{.haskell} or Monad{.haskell} instances to generate some sort of computation from each element in a container, and then perform all the side effects from those computations, discarding the results: traverse_{.haskell}, sequenceA_{.haskell}, and others. The results must be discarded because the Foldable class is too weak to specify what to do with them: we cannot, in general, make an arbitrary Applicative{.haskell} or Monad{.haskell} instance into a Monoid{.haskell}, but we can make m (){.haskell} into a Monoid{.haskell} for any such m. If we do have an Applicative{.haskell} or Monad{.haskell} with a monoid structure—that is, an Alternative{.haskell} or a MonadPlus{.haskell}—then we can use the asum{.haskell} or msum{.haskell} functions, which can combine the results as well. Consult the Foldable{.haskell} documentation for more details on any of these functions.

Note that the Foldable{.haskell} operations always forget the structure of the container being folded. If we start with a container of type t a{.haskell} for some Foldable t{.haskell}, then t will never appear in the output type of any operations defined in the Foldable{.haskell} module. Many times this is exactly what we want, but sometimes we would like to be able to generically traverse a container while preserving its structure—and this is exactly what the Traversable{.haskell} class provides, which will be discussed in the next section.

Exercises

#. Implement toList :: Foldable f => f a -> [a]{.haskell}. #. Pick some of the following functions to implement: concat{.haskell}, concatMap{.haskell}, and{.haskell}, or{.haskell}, any{.haskell}, all{.haskell}, sum{.haskell}, product{.haskell}, maximum{.haskell}(By), minimum{.haskell}(By), elem{.haskell}, notElem{.haskell}, and find{.haskell}. Figure out how they generalize to Foldable{.haskell} and come up with elegant implementations using fold{.haskell} or foldMap{.haskell} along with appropriate Monoid{.haskell} instances.

Foldable actually isn’t

The generic term “fold” is often used to refer to the more technical concept of catamorphism. Intuitively, given a way to summarize “one level of structure” (where recursive subterms have already been replaced with their summaries), a catamorphism can summarize an entire recursive structure. It is important to realize that Foldable{.haskell} does not correspond to catamorphisms, but to something weaker. In particular, Foldable{.haskell} allows observing only the left-right order of elements within a structure, not the actual structure itself. Put another way, every use of Foldable{.haskell} can be expressed in terms of toList{.haskell}. For example, fold{.haskell} itself is equivalent to mconcat . toList{.haskell}.

This is sufficient for many tasks, but not all. For example, consider trying to compute the depth of a Tree{.haskell}: try as we might, there is no way to implement it using Foldable{.haskell}. However, it can be implemented as a catamorphism.

Further reading

The Foldable{.haskell} class had its genesis in McBride and Paterson’s paper introducing Applicative{.haskell}, although it has been fleshed out quite a bit from the form in the paper.

An interesting use of Foldable{.haskell} (as well as Traversable{.haskell}) can be found in Janis Voigtländer’s paper Bidirectionalization for free!.

Traversable

Definition

The Traversable{.haskell} type class, defined in the Data.Traversable module (haddock), is:

class (Functor t, Foldable t) => Traversable t where
  traverse  :: Applicative f => (a -> f b) -> t a -> f (t b)
  sequenceA :: Applicative f => t (f a) -> f (t a)
  mapM      ::       Monad m => (a -> m b) -> t a -> m (t b)
  sequence  ::       Monad m => t (m a) -> m (t a)

As you can see, every Traversable{.haskell} is also a foldable functor. Like Foldable{.haskell}, there is a lot in this type class, but making instances is actually rather easy: one need only implement traverse{.haskell} or sequenceA{.haskell}; the other methods all have default implementations in terms of these functions. A good exercise is to figure out what the default implementations should be: given either traverse{.haskell} or sequenceA{.haskell}, how would you define the other three methods? (Hint for mapM{.haskell}: Control.Applicative exports the WrapMonad{.haskell} newtype, which makes any Monad{.haskell} into an Applicative{.haskell}. The sequence{.haskell} function can be implemented in terms of mapM{.haskell}.)

Intuition

The key method of the Traversable{.haskell} class, and the source of its unique power, is sequenceA{.haskell}. Consider its type:

  sequenceA :: Applicative f => t (f a) -> f (t a)

This answers the fundamental question: when can we commute two functors? For example, can we turn a tree of lists into a list of trees?

The ability to compose two monads depends crucially on this ability to commute functors. Intuitively, if we want to build a composed monad M a = m (n a){.haskell} out of monads m and n, then to be able to implement join :: M (M a) -> M a{.haskell}, that is, join :: m (n (m (n a))) -> m (n a){.haskell}, we have to be able to commute the n past the m to get m (m (n (n a))){.haskell}, and then we can use the join{.haskell}s for m and n to produce something of type m (n a){.haskell}. See Mark Jones’s paper for more details.

Alternatively, looking at the type of traverse{.haskell},

  traverse :: Applicative f => (a -> f b) -> t a -> f (t b)

leads us to view Traversable{.haskell} as a generalization of Functor{.haskell}. traverse{.haskell} is an “effectful fmap{.haskell}”: it allows us to map over a structure of type t a{.haskell}, applying a function to every element of type a and in order to produce a new structure of type t b{.haskell}; but along the way the function may have some effects (captured by the applicative functor f).

Exercises

#. There are at least two natural ways to turn a tree of lists into a list of trees. What are they, and why? #. Give a natural way to turn a list of trees into a tree of lists. #. What is the type of traverse . traverse{.haskell}? What does it do?

Instances and examples

What’s an example of a Traversable{.haskell} instance? The following code shows an example instance for the same Tree{.haskell} type used as an example in the previous Foldable{.haskell} section. It is instructive to compare this instance with a Functor{.haskell} instance for Tree{.haskell}, which is also shown.

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

instance Traversable Tree where
  traverse g Empty        = pure Empty
  traverse g (Leaf x)     = Leaf <$> g x
  traverse g (Node l x r) = Node <$> traverse g l
                                 <*> g x
                                 <*> traverse g r

instance Functor Tree where
  fmap     g Empty        = Empty
  fmap     g (Leaf x)     = Leaf $ g x
  fmap     g (Node l x r) = Node (fmap g l)
                                 (g x)
                                 (fmap g r)

It should be clear that the Traversable{.haskell} and Functor{.haskell} instances for Tree{.haskell} are almost identical; the only difference is that the Functor instance involves normal function application, whereas the applications in the Traversable{.haskell} instance take place within an Applicative{.haskell} context, using (<$>){.haskell} and (<*>){.haskell}. In fact, this will be true for any type.

Any Traversable{.haskell} functor is also Foldable{.haskell}, and a Functor{.haskell}. We can see this not only from the class declaration, but by the fact that we can implement the methods of both classes given only the Traversable methods.

The standard libraries provide a number of Traversable{.haskell} instances, including instances for []{.haskell}, Maybe{.haskell}, Map{.haskell}, Tree{.haskell}, and Sequence{.haskell}. Notably, Set{.haskell} is not Traversable{.haskell}, although it is Foldable{.haskell}.

Exercises

#. Implement fmap{.haskell} and foldMap{.haskell} using only the Traversable{.haskell} methods. (Note that the Traversable{.haskell} module provides these implementations as fmapDefault{.haskell} and foldMapDefault{.haskell}.)

Laws

Any instance of Traversable{.haskell} must satisfy the following two laws, where Identity{.haskell} is the identity functor (as defined in the Data.Functor.Identity module from the transformers package), and Compose{.haskell} wraps the composition of two functors (as defined in Data.Functor.Compose):

#. traverse Identity = Identity #. traverse (Compose . fmap g . f) = Compose . fmap (traverse g) . traverse f

The first law essentially says that traversals cannot make up arbitrary effects. The second law explains how doing two traversals in sequence can be collapsed to a single traversal.

Additionally, suppose eta{.haskell} is an “Applicative{.haskell} morphism”, that is,

  eta :: forall a f g. (Applicative f, Applicative g) => f a -> g a

and eta{.haskell} preserves the Applicative{.haskell} operations: eta (pure x) = pure x{.haskell} and eta (x <*> y) = eta x <*> eta y{.haskell}. Then, by parametricity, any instance of Traversable{.haskell} satisfying the above two laws will also satisfy eta . traverse f = traverse (eta . f){.haskell}.

Further reading

The Traversable{.haskell} class also had its genesis in McBride and Paterson’s Applicative{.haskell} paper, and is described in more detail in Gibbons and Oliveira, The Essence of the Iterator Pattern, which also contains a wealth of references to related work.

Traversable{.haskell} forms a core component of Edward Kmett’s lens library. Watching Edward’s talk on the subject is a highly recommended way to gain better insight into Traversable{.haskell}, Foldable{.haskell}, Applicative{.haskell}, and many other things besides.

For references on the Traversable{.haskell} laws, see Russell O’Connor’s mailing list post (and subsequent thread).

Category

Category{.haskell} is a relatively recent addition to the Haskell standard libraries. It generalizes the notion of function composition to general “morphisms”.

The definition of the Category{.haskell} type class (from Control.Category; haddock) is shown below. For ease of reading, note that I have used an infix type variable `arr`{.haskell}, in parallel with the infix function type constructor (->){.haskell}. ^[GHC 7.6.1 changed its rules regarding types and type variables. Now, any operator at the type level is treated as a type constructor rather than a type variable; prior to GHC 7.6.1 it was possible to use (~>){.haskell} instead of `arr`{.haskell}. For more information, see the discussion on the GHC-users mailing list. For a new approach to nice arrow notation that works with GHC 7.6.1, see this message and also this message from Edward Kmett, though for simplicity I haven’t adopted it here.] This syntax is not part of Haskell 2010. The second definition shown is the one used in the standard libraries. For the remainder of this document, I will use the infix type constructor `arr`{.haskell} for Category{.haskell} as well as Arrow{.haskell}.

class Category arr where
  id  :: a `arr` a
  (.) :: (b `arr` c) -> (a `arr` b) -> (a `arr` c)

-- The same thing, with a normal (prefix) type constructor
class Category cat where
  id  :: cat a a
  (.) :: cat b c -> cat a b -> cat a c

Note that an instance of Category{.haskell} should be a type constructor which takes two type arguments, that is, something of kind * -> * -> *{.haskell}. It is instructive to imagine the type constructor variable cat{.haskell} replaced by the function constructor (->): indeed, in this case we recover precisely the familiar identity function id{.haskell} and function composition operator (.){.haskell} defined in the standard Prelude{.haskell}.

Of course, the Category{.haskell} module provides exactly such an instance of Category{.haskell} for (->){.haskell}. But it also provides one other instance, shown below, which should be familiar from the previous discussion of the Monad{.haskell} laws. Kleisli m a b{.haskell}, as defined in the Control.Arrow module, is just a newtype{.haskell} wrapper around a -> m b{.haskell}.

newtype Kleisli m a b = Kleisli { runKleisli :: a -> m b }

instance Monad m => Category (Kleisli m) where
  id = Kleisli return
  Kleisli g . Kleisli h = Kleisli (h >=> g)

The only law that Category{.haskell} instances should satisfy is that id{.haskell} and (.){.haskell} should form a monoid—that is, id{.haskell} should be the identity of (.){.haskell}, and (.){.haskell} should be associative.

Finally, the Category{.haskell} module exports two additional operators: (<<<){.haskell}, which is just a synonym for (.){.haskell}, and (>>>){.haskell}, which is (.){.haskell} with its arguments reversed. (In previous versions of the libraries, these operators were defined as part of the Arrow{.haskell} class.)

Further reading

The name Category{.haskell} is a bit misleading, since the Category{.haskell} class cannot represent arbitrary categories, but only categories whose objects are objects of Hask{.haskell}, the category of Haskell types. For a more general treatment of categories within Haskell, see the category-extras package. For more about category theory in general, see the excellent Haskell wikibook page, Steve Awodey’s new book, Benjamin Pierce’s Basic category theory for computer scientists, or Barr and Wells’s category theory lecture notes. Benjamin Russell’s blog post is another good source of motivation and category theory links. You certainly don’t need to know any category theory to be a successful and productive Haskell programmer, but it does lend itself to much deeper appreciation of Haskell’s underlying theory.

Arrow

The Arrow{.haskell} class represents another abstraction of computation, in a similar vein to Monad{.haskell} and Applicative{.haskell}. However, unlike Monad and Applicative{.haskell}, whose types only reflect their output, the type of an Arrow{.haskell} computation reflects both its input and output. Arrows generalize functions: if arr{.haskell} is an instance of Arrow{.haskell}, a value of type b `arr` c{.haskell} can be thought of as a computation which takes values of type b as input, and produces values of type c as output. In the (->){.haskell} instance of Arrow{.haskell} this is just a pure function; in general, however, an arrow may represent some sort of “effectful” computation.

Definition

The definition of the Arrow{.haskell} type class, (from Control.Arrow; haddock), is:

class Category arr => Arrow arr where
  arr :: (b -> c) -> (b `arr` c)
  first :: (b `arr` c) -> ((b, d) `arr` (c, d))
  second :: (b `arr` c) -> ((d, b) `arr` (d, c))
  (***) :: (b `arr` c) -> (b' `arr` c') -> ((b, b') `arr` (c, c'))
  (&&&) :: (b `arr` c) -> (b `arr` c') -> (b `arr` (c, c'))

The first thing to note is the Category{.haskell} class constraint, which means that we get identity arrows and arrow composition for free: given two arrows g :: b `arr` c{.haskell} and h :: c `arr` d{.haskell}, we can form their composition g >>> h :: b `arr` d{.haskell} ^[In versions of the base package prior to version 4, there is no Category{.haskell} class, and the Arrow{.haskell} class includes the arrow composition operator (>>>){.haskell}. It also includes pure{.haskell} as a synonym for arr{.haskell}, but this was removed since it conflicts with the pure{.haskell} from Applicative{.haskell}.].

As should be a familiar pattern by now, the only methods which must be defined when writing a new instance of Arrow{.haskell} are arr{.haskell} and first{.haskell}; the other methods have default definitions in terms of these, but are included in the Arrow{.haskell} class so that they can be overridden with more efficient implementations if desired.

Intuition

Let’s look at each of the arrow methods in turn. Ross Paterson’s web page on arrows has nice diagrams which can help build intuition.

Instances

The Arrow{.haskell} library itself only provides two Arrow{.haskell} instances, both of which we have already seen: (->){.haskell}, the normal function constructor, and Kleisli m{.haskell}, which makes functions of type a -> m b{.haskell} into Arrow{.haskell}s for any Monad m{.haskell}. These instances are:

instance Arrow (->) where
  arr g = g
  first g (x,y) = (g x, y)

newtype Kleisli m a b = Kleisli { runKleisli :: a -> m b }

instance Monad m => Arrow (Kleisli m) where
  arr f = Kleisli (return . f)
  first (Kleisli f) = Kleisli (\ ~(b,d) -> do
                        c <- f b
                        return (c,d) )

Laws

There are quite a few laws that instances of Arrow{.haskell} should satisfy ^[See John Hughes: Generalising monads to arrows; Sam Lindley, Philip Wadler, Jeremy Yallop: The arrow calculus; Ross Paterson: Programming with Arrows.]:

arr id = id
arr (h . g) = arr g >>> arr h
first (arr g) = arr (g *** id)
first (g >>> h) = first g >>> first h
first g >>> arr (id *** h) = arr (id *** h) >>> first g
first g >>> arr fst = arr fst >>> g
first (first g) >>> arr assoc = arr assoc >>> first g

assoc ((x,y),z) = (x,(y,z))

Note that this version of the laws is slightly different than the laws given in the first two above references, since several of the laws have now been subsumed by the Category{.haskell} laws (in particular, the requirements that id{.haskell} is the identity arrow and that (>>>){.haskell} is associative). The laws shown here follow those in Paterson’s Programming with Arrows, which uses the Category{.haskell} class.

The reader is advised not to lose too much sleep over the Arrow laws ^[Unless category-theory-induced insomnolence is your cup of tea.], since it is not essential to understand them in order to program with arrows. There are also laws that ArrowChoice{.haskell}, ArrowApply{.haskell}, and ArrowLoop{.haskell} instances should satisfy; the interested reader should consult Paterson: Programming with Arrows.

ArrowChoice

Computations built using the Arrow{.haskell} class, like those built using the Applicative{.haskell} class, are rather inflexible: the structure of the computation is fixed at the outset, and there is no ability to choose between alternate execution paths based on intermediate results. The ArrowChoice{.haskell} class provides exactly such an ability:

class Arrow arr => ArrowChoice arr where
  left  :: (b `arr` c) -> (Either b d `arr` Either c d)
  right :: (b `arr` c) -> (Either d b `arr` Either d c)
  (+++) :: (b `arr` c) -> (b' `arr` c') -> (Either b b' `arr` Either c c')
  (|||) :: (b `arr` d) -> (c `arr` d) -> (Either b c `arr` d)

A comparison of ArrowChoice{.haskell} to Arrow{.haskell} will reveal a striking parallel between left{.haskell}, right{.haskell}, (+++){.haskell}, (|||){.haskell} and first{.haskell}, second{.haskell}, (***){.haskell}, (&&&){.haskell}, respectively. Indeed, they are dual: first{.haskell}, second{.haskell}, (***){.haskell}, and (&&&){.haskell} all operate on product types (tuples), and left{.haskell}, right{.haskell}, (+++){.haskell}, and (|||){.haskell} are the corresponding operations on sum types. In general, these operations create arrows whose inputs are tagged with Left{.haskell} or Right{.haskell}, and can choose how to act based on these tags.

The ArrowChoice{.haskell} class allows computations to choose among a finite number of execution paths, based on intermediate results. The possible execution paths must be known in advance, and explicitly assembled with (+++){.haskell} or (|||){.haskell}. However, sometimes more flexibility is needed: we would like to be able to compute an arrow from intermediate results, and use this computed arrow to continue the computation. This is the power given to us by ArrowApply{.haskell}.

ArrowApply

The ArrowApply{.haskell} type class is:

class Arrow arr => ArrowApply arr where
  app :: (b `arr` c, b) `arr` c

If we have computed an arrow as the output of some previous computation, then app{.haskell} allows us to apply that arrow to an input, producing its output as the output of app{.haskell}. As an exercise, the reader may wish to use app{.haskell} to implement an alternative “curried” version, app2 :: b `arr` ((b `arr` c) `arr` c){.haskell}.

This notion of being able to compute a new computation may sound familiar: this is exactly what the monadic bind operator (>>=){.haskell} does. It should not particularly come as a surprise that ArrowApply{.haskell} and Monad{.haskell} are exactly equivalent in expressive power. In particular, Kleisli m{.haskell} can be made an instance of ArrowApply{.haskell}, and any instance of ArrowApply{.haskell} can be made a Monad{.haskell} (via the newtype{.haskell} wrapper ArrowMonad{.haskell}). As an exercise, the reader may wish to try implementing these instances:

instance Monad m => ArrowApply (Kleisli m) where
  app =    -- exercise

newtype ArrowApply a => ArrowMonad a b = ArrowMonad (a () b)

instance ArrowApply a => Monad (ArrowMonad a) where
  return               =    -- exercise
  (ArrowMonad a) >>= k =    -- exercise

ArrowLoop

The ArrowLoop{.haskell} type class is:

class Arrow a => ArrowLoop a where
  loop :: a (b, d) (c, d) -> a b c

trace :: ((b,d) -> (c,d)) -> b -> c
trace f b = let (c,d) = f (b,d) in c

It describes arrows that can use recursion to compute results, and is used to desugar the rec construct in arrow notation (described below).

Taken by itself, the type of the loop{.haskell} method does not seem to tell us much. Its intention, however, is a generalization of the trace function which is also shown. The d component of the first arrow’s output is fed back in as its own input. In other words, the arrow loop g{.haskell} is obtained by recursively “fixing” the second component of the input to g.

It can be a bit difficult to grok what the trace{.haskell} function is doing. How can d appear on the left and right sides of the let{.haskell}? Well, this is Haskell’s laziness at work. There is not space here for a full explanation; the interested reader is encouraged to study the standard fix{.haskell} function, and to read Paterson’s arrow tutorial.

Arrow notation

Programming directly with the arrow combinators can be painful, especially when writing complex computations which need to retain simultaneous reference to a number of intermediate results. With nothing but the arrow combinators, such intermediate results must be kept in nested tuples, and it is up to the programmer to remember which intermediate results are in which components, and to swap, reassociate, and generally mangle tuples as necessary. This problem is solved by the special arrow notation supported by GHC, similar to do notation for monads, that allows names to be assigned to intermediate results while building up arrow computations. An example arrow implemented using arrow notation, taken from Paterson, is:

class ArrowLoop arr => ArrowCircuit arr where
  delay :: b -> (b `arr` b)

counter :: ArrowCircuit arr => Bool `arr` Int
counter = proc reset -> do
            rec output <- idA     -< if reset
                                        then 0
                                        else next
                next   <- delay 0 -< output + 1
            idA -< output

This arrow is intended to represent a recursively defined counter circuit with a reset line.

There is not space here for a full explanation of arrow notation; the interested reader should consult Paterson’s paper introducing the notation, or his later tutorial which presents a simplified version.

Further reading

An excellent starting place for the student of arrows is the arrows web page, which contains an introduction and many references. Some key papers on arrows include Hughes’s original paper introducing arrows, Generalising monads to arrows, and Paterson’s paper on arrow notation.

Both Hughes and Paterson later wrote accessible tutorials intended for a broader audience: Paterson: Programming with Arrows and Hughes: Programming with Arrows.

Although Hughes’s goal in defining the Arrow{.haskell} class was to generalize Monad{.haskell}s, and it has been said that Arrow{.haskell} lies “between Applicative{.haskell} and Monad{.haskell}” in power, they are not directly comparable. The precise relationship remained in some confusion until analyzed by Lindley, Wadler, and Yallop, who also invented a new calculus of arrows, based on the lambda calculus, which considerably simplifies the presentation of the arrow laws (see The arrow calculus). There is also a precise technical sense in which Arrow{.haskell} can be seen as the intersection of Applicative{.haskell} and Category{.haskell}.

Some examples of Arrow{.haskell}s include Yampa, the Haskell XML Toolkit, and the functional GUI library Grapefruit.

Some extensions to arrows have been explored; for example, the BiArrow{.haskell}s of Alimarine et al., for two-way instead of one-way computation.

The Haskell wiki has [links to many additional research papers relating to Arrow{.haskell}s](http://www.haskell.org/haskellwiki/Research papers/Monads and Arrows).

Comonad

The final type class we will examine is Comonad{.haskell}. The Comonad{.haskell} class is the categorical dual of Monad{.haskell}; that is, Comonad{.haskell} is like Monad but with all the function arrows flipped. It is not actually in the standard Haskell libraries, but it has seen some interesting uses recently, so we include it here for completeness.

Definition

The Comonad{.haskell} type class, defined in the Control.Comonad module of the comonad library, is:

class Functor w => Comonad w where
  extract :: w a -> a

  duplicate :: w a -> w (w a)
  duplicate = extend id

  extend :: (w a -> b) -> w a -> w b
  extend f = fmap f . duplicate

As you can see, extract{.haskell} is the dual of return{.haskell}, duplicate{.haskell} is the dual of join{.haskell}, and extend{.haskell} is the dual of (=<<){.haskell}. The definition of Comonad{.haskell} is a bit redundant, giving the programmer the choice on whether extend or duplicate are implemented; the other operation then has a default implementation.

A prototypical example of a Comonad{.haskell} instance is:

-- Infinite lazy streams
data Stream a = Cons a (Stream a)

-- 'duplicate' is like the list function 'tails'
-- 'extend' computes a new Stream from an old, where the element
--   at position n is computed as a function of everything from
--   position n onwards in the old Stream
instance Comonad Stream where
  extract (Cons x _) = x
  duplicate s@(Cons x xs) = Cons s (duplicate xs)
  extend g s@(Cons x xs)  = Cons (g s) (extend g xs)
                       -- = fmap g (duplicate s)

Further reading

Dan Piponi explains in a blog post what cellular automata have to do with comonads. In another blog post, Conal Elliott has examined a comonadic formulation of functional reactive programming. Sterling Clover’s blog post Comonads in everyday life explains the relationship between comonads and zippers, and how comonads can be used to design a menu system for a web site.

Uustalu and Vene have a number of papers exploring ideas related to comonads and functional programming:

Gabriel Gonzalez’s Comonads are objects points out similarities between comonads and object-oriented programming.

The comonad-transformers package contains comonad transformers.

Acknowledgements

A special thanks to all of those who taught me about standard Haskell type classes and helped me develop good intuition for them, particularly Jules Bean (quicksilver), Derek Elkins (ddarius), Conal Elliott (conal), Cale Gibbard (Cale), David House, Dan Piponi (sigfpe), and Kevin Reid (kpreid).

I also thank the many people who provided a mountain of helpful feedback and suggestions on a first draft of the Typeclassopedia: David Amos, Kevin Ballard, Reid Barton, Doug Beardsley, Joachim Breitner, Andrew Cave, David Christiansen, Gregory Collins, Mark Jason Dominus, Conal Elliott, Yitz Gale, George Giorgidze, Steven Grady, Travis Hartwell, Steve Hicks, Philip Hölzenspies, Edward Kmett, Eric Kow, Serge Le Huitouze, Felipe Lessa, Stefan Ljungstrand, Eric Macaulay, Rob MacAulay, Simon Meier, Eric Mertens, Tim Newsham, Russell O’Connor, Conrad Parker, Walt Rorie-Baety, Colin Ross, Tom Schrijvers, Aditya Siram, C. Smith, Martijn van Steenbergen, Joe Thornber, Jared Updike, Rob Vollmert, Andrew Wagner, Louis Wasserman, and Ashley Yakeley, as well as a few only known to me by their IRC nicks: b_jonas, maltem, tehgeekmeister, and ziman. I have undoubtedly omitted a few inadvertently, which in no way diminishes my gratitude.

Finally, I would like to thank Wouter Swierstra for his fantastic work editing the Monad.Reader, and my wife Joyia for her patience during the process of writing the Typeclassopedia.

About the author

Brent Yorgey (blog, homepage) is (as of September 2013) a Ph.D. student in the programming languages group at the University of Pennsylvania. He enjoys teaching, creating EDSLs, playing Bach fugues, musing upon category theory, and cooking tasty lambda-treats for the denizens of #haskell.

Colophon

The Typeclassopedia was written by Brent Yorgey and initially published in March 2009. It was converted to wiki syntax by Geheimdienst in November 2011, after asking Brent’s permission. The Markdown conversion was done by Erlend Hamberg and the EPUB file is generated by the excellent pandoc tool written by John MacFarlane.