Haskell/Traversable

We already have studied four of the five type classes in the Prelude that can be used for data structure manipulation: Functor, Applicative, Monad and Foldable. The fifth one is Traversable [1]. To traverse means to walk across, and that is exactly what Traversable generalises: walking across a structure, collecting results at each stop.

Functors made for walking edit

If traversing means walking across, though, we have been performing traversals for a long time already. Consider the following plausible Functor and Foldable instances for lists:

instance Functor [] where
    fmap _ []     = []
    fmap f (x:xs) = f x : fmap f xs

instance Foldable [] where
    foldMap _ []     = mempty
    foldMap f (x:xs) = f x <> foldMap f xs

fmap f walks across the list, applies f to each element and collects the results by rebuilding the list. Similarly, foldMap f walks across the list, applies f to each element and collects the results by combining them with mappend. Functor and Foldable, however, are not enough to express all useful ways of traversing. For instance, suppose we have the following Maybe-encoded test for negative numbers...

deleteIfNegative :: (Num a, Ord a) => a -> Maybe a
deleteIfNegative x = if x < 0 then Nothing else Just x

... and we want to use it to implement...

rejectWithNegatives :: (Num a, Ord a) => [a] -> Maybe [a]

... which gives back the original list wrapped in Just if there are no negative elements in it, and Nothing otherwise. Neither Foldable nor Functor on their own would help. Using Foldable would replace the structure of the original list with that of whatever Monoid we pick for folding, and there is no way of twisting that into giving either the original list or Nothing [2]. As for Functor, fmap might be attractive at first...

GHCi> let testList = [-5,3,2,-1,0]
GHCi> fmap deleteIfNegative testList
[Nothing,Just 3,Just 2,Nothing,Just 0]

... but then we would need a way to turn a list of Maybe into Maybe a list. If you squint hard enough, that looks somewhat like a fold. Instead, however, of merely combining the values and destroying the list, we need to combine the Maybe contexts of the values and recreate the list structure within the combined context. Fortunately, there is a type class which is essentially about combining Functor contexts: Applicative [3]. Applicative, in turn, leads us to the class we need: Traversable.

instance Traversable [] where
    -- sequenceA :: Applicative f => [f a] -> f [a]
    sequenceA []     = pure []
    sequenceA (u:us) = (:) <$> u <*> sequenceA us

-- Or, equivalently:
instance Traversable [] where
    sequenceA us = foldr (\u v -> (:) <$> u <*> v) (pure []) us

Traversable is to Applicative contexts what Foldable is to Monoid values. From that point of view, sequenceA is analogous to fold − it creates an applicative summary of the contexts within a structure, and then rebuilds the structure in the new context. sequenceA is the function we were looking for:

GHCi> let rejectWithNegatives = sequenceA . fmap deleteIfNegative
GHCi> :t rejectWithNegatives 
rejectWithNegatives
  :: (Num a, Ord a, Traversable t) => t a -> Maybe (t a)
GHCi> rejectWithNegatives testList
Nothing
GHCi> rejectWithNegatives [0..10]
Just [0,1,2,3,4,5,6,7,8,9,10]

These are the methods of Traversable:

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)

    -- These methods have default definitions.
    -- They are merely specialised versions of the other two.
    mapM      :: Monad m => (a -> m b) -> t a -> m (t b)
    sequence  :: Monad m => t (m a) -> m (t a)

If sequenceA is analogous to fold, traverse is analogous to foldMap. They can be defined in terms of each other, and therefore a minimal implementation of Traversable just needs to supply one of them:

traverse f = sequenceA . fmap f
sequenceA = traverse id

Rewriting the list instance using traverse makes the parallels with Functor and Foldable obvious:

instance Traversable [] where
    traverse _ []     = pure []
    traverse f (x:xs) = (:) <$> f x <*> traverse f xs

-- Or, equivalently:
instance Traversable [] where
    traverse f xs = foldr (\x v -> (:) <$> f x <*> v) (pure []) xs

In general, it is better to write traverse when implementing Traversable, as the default definition of traverse performs, in principle, two runs across the structure (one for fmap and another for sequenceA).

We can cleanly define rejectWithNegatives directly in terms of traverse:

rejectWithNegatives :: (Num a, Ord a, Traversable t) => t a -> Maybe (t a)
rejectWithNegatives = traverse deleteIfNegative
Exercises
  1. Give the Tree from Other data structures a Traversable instance. The definition of Tree is:
    data Tree a = Leaf a | Branch (Tree a) (Tree a)

Interpretations of Traversable edit

Traversable structures can be walked over using the applicative functor of your choice. The type of traverse...

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

... resembles that of mapping functions we have seen in other classes. Rather than using its function argument to insert functorial contexts under the original structure (as might be done with fmap) or to modify the structure itself (as (>>=) does), traverse adds an extra layer of context on the top of the structure. Said in another way, traverse allows for effectful traversals − traversals which produce an overall effect (i.e. the new outer layer of context).

If the structure below the new layer is recoverable at all, it will match the original structure (the values might have changed, of course). Here is an example involving nested lists:

GHCi> traverse (\x -> [0..x]) [0..2]
[[0,0,0],[0,0,1],[0,0,2],[0,1,0],[0,1,1],[0,1,2]]

To understand what is going on here, let's break this down step by step.

traverse (\x -> [0..x]) [0..2]
sequenceA $ fmap (\x -> [0..x]) [0..2]
sequenceA [[0],[0,1],[0,1,2]]
(:) <$> [0] <*> ((:) <$> [0,1] <*> ((:) <$> [0,1,2] <*> pure []))
(:) <$> [0] <*> ((:) <$> [0,1] <*> ([[0],[1],[2]]))
(:) <$> [0] <*> ([[0,0],[0,1],[0,2],[1,0],[1,1],[1,2]])
[[0,0,0],[0,0,1],[0,0,2],[0,1,0],[0,1,1],[0,1,2]]

The inner lists retain the structure of the original list − all of them have three elements. The outer list is the new layer, corresponding to the introduction of nondeterminism through allowing each element to vary from zero to its (original) value.

We can also understand Traversable by focusing on sequenceA and how it distributes context.

GHCi> sequenceA [[1,2,3,4],[5,6,7]]
[[1,5],[1,6],[1,7],[2,5],[2,6],[2,7]
,[3,5],[3,6],[3,7],[4,5],[4,6],[4,7]
]

In this example, sequenceA can be seen distributing the old outer structure into the new outer structure, and so the new inner lists have two elements, just like the old outer list. The new outer structure is a list of twelve elements, which is exactly what you would expect from combining with (<*>) one list of four elements with another of three elements. One interesting aspect of the distribution perspective is how it helps making sense of why certain functors cannot possibly have instances of Traversable (how would one distribute an IO action? Or a function?).

Exercises

Having the applicative functors chapter fresh in memory can help with the following exercises.

  1. Consider a representation of matrices as nested lists, with the inner lists being the rows. Use Traversable to implement
    transpose :: [[a]] -> [[a]]
    which transposes a matrix (i.e. changes columns into rows and vice-versa). For the purposes of this exercise, we don't care about how fake "matrices" with rows of different sizes are handled.
  2. Explain what traverse mappend does.
  3. Time for a round of Spot The Applicative Functor. Consider:
    mapAccumL :: Traversable t =>
    (a -> b -> (a, c)) -> a -> t b -> (a, t c)

    Does its type remind you of anything? Use the appropriate Applicative to implement it with Traversable. As further guidance, here is the description of mapAccumL in the Data.Traversable documentation:

    The mapAccumL function behaves like a combination of fmap and foldl; it applies a function to each element of a structure, passing an accumulating parameter from left to right, and returning a final value of this accumulator together with the new structure.

The Traversable laws edit

Sensible instances of Traversable have a set of laws to follow. There are the following two laws:

traverse Identity = Identity -- identity
traverse (Compose . fmap g . f) = Compose . fmap (traverse g) . traverse f -- composition

Plus a bonus law, which is guaranteed to hold:

-- If t is an applicative homomorphism, then
t . traverse f = traverse (t . f) -- naturality

Those laws are not exactly self-explanatory, so let's have a closer look at them. Starting from the last one: an applicative homomorphism is a function which preserves the Applicative operations, so that:

-- Given a choice of f and g, and for any a,
t :: (Applicative f, Applicative g) => f a -> g a

t (pure x) = pure x
t (x <*> y) = t x <*> t y

Note that not only this definition is analogous to the one of monoid homomorphisms which we have seen earlier on but also that the naturality law mirrors exactly the property about foldMap and monoid homomorphisms seen in the chapter about Foldable.

The identity law involves Identity, the dummy functor:

newtype Identity a = Identity { runIdentity :: a }

instance Functor Identity where
    fmap f (Identity x) = Identity (f x)

instance Applicative Identity where
    pure x = Identity x
    Identity f <*> Identity x = Identity (f x)

The law says that all traversing with the Identity constructor does is wrap the structure with Identity, which amounts to doing nothing (as the original structure can be trivially recovered with runIdentity). The Identity constructor is thus the identity traversal, which is very reasonable indeed.

The composition law, in turn, is stated in terms of the Compose functor:

newtype Compose f g a = Compose { getCompose :: f (g a) }

instance (Functor f, Functor g) => Functor (Compose f g) where
    fmap f (Compose x) = Compose (fmap (fmap f) x)

instance (Applicative f, Applicative g) => Applicative (Compose f g) where
    pure x = Compose (pure (pure x))
    Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)

Compose performs composition of functors. Composing two Functors results in a Functor, and composing two Applicatives results in an Applicative [4]. The instances are the obvious ones, threading the methods one further functorial layer down.

The composition law states that it doesn't matter whether we perform two traversals separately (right side of the equation) or compose them in order to walk across the structure only once (left side). It is analogous, for instance, to the second functor law. The fmaps are needed because the second traversal (or the second part of the traversal, for the left side of the equation) happens below the layer of structure added by the first (part). Compose is needed so that the composed traversal is applied to the correct layer.

Identity and Compose are available from Data.Functor.Identity and Data.Functor.Compose respectively.

The laws can also be formulated in terms of sequenceA:

sequenceA . fmap Identity = Identity -- identity
sequenceA . fmap Compose = Compose . fmap sequenceA . sequenceA -- composition
-- For any applicative homomorphism t:
t . sequenceA = sequenceA . fmap t -- naturality

Though it's not immediately obvious, several desirable characteristics of traversals follow from the laws, including [5]:

  • Traversals do not skip elements.
  • Traversals do not visit elements more than once.
  • traverse pure = pure
  • Traversals cannot modify the original structure (it is either preserved or fully destroyed).

Recovering fmap and foldMap edit

We still have not justified the Functor and Foldable class constraints of Traversable. The reason for them is very simple: as long as the Traversable instance follows the laws traverse is enough to implement both fmap and foldMap. For fmap, all we need is to use Identity to make a traversal out of an arbitrary function:

fmap f = runIdentity . traverse (Identity . f)

To recover foldMap, we need to introduce a third utility functor: Const from Control-Applicative:

newtype Const a b = Const { getConst :: a }

instance Functor (Const a) where
    fmap _ (Const x) = Const x

Const is a constant functor. A value of type Const a b does not actually contain a b value. Rather, it holds an a value which is unaffected by fmap. For our current purposes, the truly interesting instance is the Applicative one

instance Monoid a => Applicative (Const a) where
    pure _ = Const mempty
    Const x <*> Const y = Const (x `mappend` y)

(<*>) simply combines the values in each context with mappend [6]. We can exploit that to make a traversal out of any Monoid m => a -> m function that we might pass to foldMap. Thanks to the instance above, the traversal then becomes a fold:

foldMap f = getConst . traverse (Const . f)

We have just recovered from traverse two functions which on the surface appear to be entirely different, and all we had to do was pick two different functors. That is a taste of how powerful an abstraction functors are [7].

Notes

  1. Strictly speaking, we should refer to the five classes in the GHC Prelude, as Applicative, Foldable and Traversable aren't officially part of the Prelude yet according to the Haskell Report. It is just a matter of time for them to be included, though.
  2. One thing to attempt would be exploiting the Monoid a => Monoid (Maybe a) instance from Data.Monoid. If you try that, however, you will see it can't possibly give the desired results.
  3. The monoidal presentation of Applicative makes that very clear.
  4. Remarkably, however, composing two Monads does not necessarily result in a Monad.
  5. For technical details, check the papers cited by the Data.Traversable documentation.
  6. This is a great illustration of how Applicative combines contexts monoidally. If we remove the values within the context, the applicative laws in monoidal presentation match the monoid laws exactly.
  7. A prime example, and one of clear practical relevance at that, is that great ode to functors, the lens library.