14 min read

 In this article by Ryan Lemmer, author of the book Haskell Design Patterns, we will focus on two fundamental patterns of recursion: fold and map. The more primitive forms of these patterns are to be found in the Prelude, the “old part” of Haskell.

With the introduction of Applicative, came more powerful mapping (traversal), which opened the door to type-level folding and mapping in Haskell. First, we will look at how Prelude’s list fold is generalized to all Foldable containers. Then, we will follow the generalization of list map to all Traversable containers.

Our exploration of fold and map culminates with the Lens library, which raises Foldable and Traversable to an even higher level of abstraction and power.

In this article, we will cover the following:

  • Traversable
  • Modernizing Haskell
  • Lenses

(For more resources related to this topic, see here.)

Traversable

As with Prelude.foldM, mapM fails us beyond lists, for example, we cannot mapM over the Tree from earlier:

main = mapM doF aTree >>= print
-- INVALID

The Traversable type-class is to map in the same way as Foldable is to fold:

-- required: traverse or sequenceA
class (Functor t, Foldable t) => Traversable (t :: * -> *) where
-- APPLICATIVE form
traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
sequenceA :: Applicative f => t (f a) -> f (t a)

-- MONADIC form (redundant)
mapM     :: Monad m   => (a -> m b) -> t a -> m (t b)
sequence :: Monad m   => t (m a) -> m (t a)

The traverse fuction generalizes our mapA function, which was written for lists, to all Traversable containers. Similarly, Traversable.mapM is a more general version of Prelude.mapM for lists:

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

The Traversable type-class was introduced along with Applicative:

“we introduce the type class Traversable, capturing functorial data structures through which we can thread an applicative computation”

                        Applicative Programming with Effects – McBride and Paterson

A Traversable Tree

Let’s make our Traversable Tree. First, we’ll do it the hard way:

– a Traversable must also be a Functor and Foldable:
instance Functor Tree where
fmap f (Leaf x) = Leaf (f x)
fmap f (Node x lTree rTree)
 = Node (f x)
    (fmap f lTree)
   (fmap f rTree)

instance Foldable Tree where
foldMap f (Leaf x) = f x
foldMap f (Node x lTree rTree)
 = (foldMap f lTree)
  `mappend` (f x)
  `mappend` (foldMap f rTree)

--traverse :: Applicative ma => (a -> ma b) -> mt a -> ma (mt b)
instance Traversable Tree where
traverse g (Leaf x) = Leaf <$> (g x)
traverse g (Node x ltree rtree)
 = Node <$> (g x)
  <*> (traverse g ltree) <*> (traverse g rtree)

data Tree a = Node a (Tree a) (Tree a) | Leaf a
deriving (Show)

 

aTree = Node 2 (Leaf 3)

    (Node 5 (Leaf 7) (Leaf 11))

-- import Data.Traversable
main = traverse doF aTree
where doF n = do print n; return (n * 2)

The easier way to do this is to auto-implement Functor, Foldable, and Traversable:

{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveTraversable #-}
import Data.Traversable

data Tree a = Node a (Tree a) (Tree a)| Leaf a
deriving (Show, Functor, Foldable, Traversable)

aTree = Node 2 (Leaf 3)
    (Node 5 (Leaf 7) (Leaf 11))

main = traverse doF aTree
where doF n = do print n; return (n * 2)

Traversal and the Iterator pattern

The Gang of Four Iterator pattern is concerned with providing a way

“…to access the elements of an aggregate object sequentially without exposing its underlying representation”

                                      “Gang of Four” Design Patterns, Gamma et al, 1995

In The Essence of the Iterator Pattern, Jeremy Gibbons shows precisely how the Applicative traversal captures the Iterator pattern.

The Traversable.traverse class is the Applicative version of Traversable.mapM, which means it is more general than mapM (because Applicative is more general than Monad).

Moreover, because mapM does not rely on the Monadic bind chain to communicate between iteration steps, Monad is a superfluous type for mapping with effects (Applicative is sufficient). In other words, Applicative traverse is superior to Monadic traversal (mapM):

“In addition to being parametrically polymorphic in the collection elements, the generic traverse operation is parametrised along two further dimensions: the datatype being tra- versed, and the applicative functor in which the traversal is interpreted”

“The improved compositionality of applicative functors over monads provides better glue for fusion of traversals, and hence better support for modular programming of iterations”

                                       The Essence of the Iterator Pattern – Jeremy Gibbons

Modernizing Haskell 98

The introduction of Applicative, along with Foldable and Traversable, had a big impact on Haskell.

Foldable and Traversable lift Prelude fold and map to a much higher level of abstraction. Moreover, Foldable and Traversable also bring a clean separation between processes that preserve or discard the shape of the structure that is being processed.

Traversable describes processes that preserve that shape of the data structure being traversed over. Foldable processes, in turn, discard or transform the shape of the structure being folded over.

Since Traversable is a specialization of Foldable, we can say that shape preservation is a special case of shape transformation. This line between shape preservation and transformation is clearly visible from the fact that functions that discard their results (for example, mapM_, forM_, sequence_, and so on) are in Foldable, while their shape-preserving counterparts are in Traversable.

Due to the relatively late introduction of Applicative, the benefits of Applicative, Foldable, and Traversable have not found their way into the core of the language.

This is due to the change with the Foldable Traversable In Prelude proposal (planned for inclusion in the core libraries from GHC 7.10). For more information, visit https://wiki.haskell.org/Foldable_Traversable_In_Prelude.

This will involve replacing less generic functions in Prelude, Control.Monad, and Data.List with their more polymorphic counterparts in Foldable and Traversable.

There have been objections to the movement to modernize, the main concern being that more generic types are harder to understand, which may compromise Haskell as a learning language. These valid concerns will indeed have to be addressed, but it seems certain that the Haskell community will not resist climbing to new abstract heights.

Lenses

A Lens is a type that provides access to a particular part of a data structure.

Lenses express a high-level pattern for composition. However, Lens is also deeply entwined with Traversable, and so we describe it in this article instead.

Lenses relate to the getter and setter functions, which also describe access to parts of data structures. To find our way to the Lens abstraction (as per Edward Kmett’s Lens library), we’ll start by writing a getter and setter to access the root node of a Tree.

Deriving Lens

Returning to our Tree from earlier:

data Tree a = Node a (Tree a) (Tree a)
 | Leaf a
deriving (Show)

intTree
= Node 2 (Leaf 3)
    (Node 5 (Leaf 7)
       (Leaf 11))

listTree
= Node [1,1] (Leaf [2,1])
   (Node [3,2] (Leaf [5,2])                (Leaf [7,4]))

tupleTree
= Node (1,1) (Leaf (2,1))
   (Node (3,2) (Leaf (5,2))
     (Leaf (7,4)))

Let’s start by writing generic getter and setter functions:

getRoot :: Tree a   -> a
getRoot (Leaf z)   = z
getRoot (Node z _ _) = z

setRoot :: Tree a -> a -> Tree a
setRoot (Leaf z)     x = Leaf x
setRoot (Node z l r) x = Node x l r

main = do
print $ getRoot intTree
print $ setRoot intTree 11
print $ getRoot (setRoot intTree 11)

If we want to pass in a setter function instead of setting a value, we use the following:

fmapRoot :: (a -> a) -> Tree a -> Tree a
fmapRoot f tree = setRoot tree newRoot
where newRoot = f (getRoot tree)

We have to do a get, apply the function, and then set the result. This double work is akin to the double traversal we saw when writing traverse in terms of sequenceA. In that case we resolved the issue by defining traverse first (and then sequenceA i.t.o. traverse):

We can do the same thing here by writing fmapRoot to work in a single step (and then rewriting setRoot’ i.t.o. fmapRoot’):

fmapRoot' :: (a -> a) -> Tree a -> Tree a
fmapRoot' f (Leaf z)     = Leaf (f z)
fmapRoot' f (Node z l r) = Node (f z) l r

setRoot' :: Tree a -> a -> Tree a
setRoot' tree x = fmapRoot' (_ -> x) tree

main = do
print $ setRoot' intTree 11
print $ fmapRoot' (*2) intTree

The fmapRoot’ function delivers a function to a particular part of the structure and returns the same structure:

fmapRoot' :: (a -> a) -> Tree a -> Tree a

To allow for I/O, we need a new function:

fmapRootIO :: (a -> IO a) -> Tree a -> IO (Tree a)

We can generalize this beyond I/O to all Monads:

fmapM :: (a -> m a) -> Tree a -> m (Tree a)

It turns out that if we relax the requirement for Monad, and generalize f’ to all the Functor container types, then we get a simple van Laarhoven Lens!

type Lens' s a = Functor f' =>
   (a -> f' a) -> s -> f' s

The remarkable thing about a van Laarhoven Lens is that given the preceding function type, we also gain “get“, “set“, “fmap“, “mapM“, and many other functions and operators.

The Lens function type signature is all it takes to make something a Lens that can be used with the Lens library. It is unusual to use a type signature as “primary interface” for a library. The immediate benefit is that we can define a lens without referring to the Lens library.

We’ll explore more benefits and costs to this approach, but first let’s write a few lenses for our Tree.

The derivation of the Lens abstraction used here has been based on Jakub Arnold’s Lens tutorial, which is available at http://blog.jakubarnold.cz/2014/07/14/lens-tutorial-introduction-part-1.html.

Writing a Lens

A Lens is said to provide focus on an element in a data structure. Our first lens will focus on the root node of a Tree. Using the lens type signature as our guide, we arrive at:

lens':: Functor f => (a -> f' a) -> s     -> f' s
root :: Functor f' => (a -> f' a) -> Tree a -> f' (Tree a)

Still, this is not very tangible; fmapRootIO is easier to understand with the Functor f’ being IO:

fmapRootIO :: (a -> IO a) -> Tree a -> IO (Tree a)
fmapRootIO g (Leaf z)     = (g z) >>= return . Leaf
fmapRootIO g (Node z l r) = (g z) >>= return . (x -> Node x l r)

displayM x = print x >> return x

main = fmapRootIO displayM intTree

If we drop down from Monad into Functor, we have a Lens for the root of a Tree:

root :: Functor f' => (a -> f' a) -> Tree a -> f' (Tree a)
root g (Node z l r) = fmap (x -> Node x l r) (g z)
root g (Leaf z) = fmap Leaf               (g z)

As Monad is a Functor, this function also works with Monadic functions:

main = root displayM intTree

As root is a lens, the Lens library gives us the following:

-– import Control.Lens
main = do
-- GET
print $ view root listTree
print $ view root intTree
-- SET
print $ set root [42] listTree
print $ set root 42   intTree
-- FMAP
print $ over root (+11) intTree

The over is the lens way of fmap’ing a function into a Functor.

Composable getters and setters

Another Lens on Tree might be to focus on the rightmost leaf:

rightMost :: Functor f' =>
(a -> f' a) -> Tree a -> f' (Tree a)

rightMost g (Node z l r)
= fmap (r' -> Node z l r') (rightMost g r)
rightMost g (Leaf z)   
= fmap (x -> Leaf x) (g z)

The Lens library provides several lenses for Tuple (for example, _1 which brings focus to the first Tuple element). We can compose our rightMost lens with the Tuple lenses:

main = do
print $ view rightMost tupleTree
print $ set rightMost (0,0) tupleTree

-- Compose Getters and Setters
print $ view (rightMost._1) tupleTree
print $ set (rightMost._1) 0 tupleTree
print $ over (rightMost._1) (*100) tupleTree

A Lens can serve as a getter, setter, or “function setter”. We are composing lenses using regular function composition (.)! Note that the order of composition is reversed in (rightMost._1) the rightMost lens is applied before the _1 lens.

Lens Traversal

A Lens focuses on one part of a data structure, not several, for example, a lens cannot focus on all the leaves of a Tree:

set leaves 0 intTree
over leaves (+1) intTree

To focus on more than one part of a structure, we need a Traversal class, the Lens generalization of Traversable). Whereas Lens relies on Functor, Traversal relies on Applicative. Other than this, the signatures are exactly the same:

traversal :: Applicative f' =>
 (a -> f' a) -> Tree a -> f' (Tree a)
lens :: Functor f'=>
 (a -> f' a) -> Tree a -> f' (Tree a)

A leaves Traversal delivers the setter function to all the leaves of the Tree:

leaves :: Applicative f' => (a -> f' a) -> Tree a -> f' (Tree a)
leaves g (Node z l r)
= Node z <$> leaves g l <*> leaves g r
leaves g (Leaf z)   
= Leaf <$> (g z)

We can use set and over functions with our new Traversal class:

set leaves 0 intTree
over leaves (+1) intTree

The Traversals class compose seamlessly with Lenses:

main = do
-- Compose Traversal + Lens
print $ over (leaves._1) (*100) tupleTree
-- Compose Traversal + Traversal
print $ over (leaves.both) (*100) tupleTree

-- map over each elem in target container (e.g. list)
print $ over (leaves.mapped) (*(-1)) listTree

-- Traversal with effects
mapMOf leaves displayM tupleTree

(The both is a Tuple Traversal that focuses on both elements).

Lens.Fold

The Lens.Traversal lifts Traversable into the realm of lenses:

main = do
print $ sumOf leaves intTree
print $ anyOf leaves (>0) intTree

The Lens Library

We used only “simple” Lenses so far. A fully parametrized Lens allows for replacing parts of a data structure with different types:

type Lens s t a b = Functor f' => (a -> f' b) -> s -> f' t
–- vs simple Lens
type Lens' s a = Lens s s a a

Lens library function names do their best to not clash with existing names, for example, postfixing of idiomatic function names with “Of” (sumOf, mapMOf, and so on), or using different verb forms such as “droppingWhile” instead of “dropWhile”. While this creates a burden as i.t.o has to learn new variations, it does have a big plus point—it allows for easy unqualified import of the Lens library.

By leaving the Lens function type transparent (and not obfuscating it with a new type), we get Traversals by simply swapping out Functor for Applicative. We also get to define lenses without having to reference the Lens library. On the downside, Lens type signatures can be bewildering at first sight. They form a language of their own that requires effort to get used to, for example:

mapMOf :: Profunctor p =>
Over p (WrappedMonad m) s t a b -> p a (m b) -> s -> m t

foldMapOf :: Profunctor p =>
Accessing p r s a -> p a r -> s -> r

On the surface, the Lens library gives us composable getters and setters, but there is much more to Lenses than that. By generalizing Foldable and Traversable into Lens abstractions, the Lens library lifts Getters, Setters, Lenses, and Traversals into a unified framework in which they are all compose together.

Edward Kmett’s Lens library is a sprawling masterpiece that is sure to leave a lasting impact on idiomatic Haskell.

Summary

We started with Lists (Haskel 98), then generalizing for all Traversable containers (Introduced in the mid-2000s).

Following that, we saw how the Lens library (2012) places traversing in an even broader context. Lenses give us a unified vocabulary to navigate data structures, which explains why it has been described as a “query language for data structures”.

Resources for Article:


Further resources on this subject:


LEAVE A REPLY

Please enter your comment!
Please enter your name here