IanG on Tap

Ian Griffiths in Weblog Form (RSS 2.0)

Blog Navigation

April (2018)

(1 item)

August (2014)

(1 item)

July (2014)

(5 items)

April (2014)

(1 item)

March (2014)

(1 item)

January (2014)

(2 items)

November (2013)

(2 items)

July (2013)

(4 items)

April (2013)

(1 item)

February (2013)

(6 items)

September (2011)

(2 items)

November (2010)

(4 items)

September (2010)

(1 item)

August (2010)

(4 items)

July (2010)

(2 items)

September (2009)

(1 item)

June (2009)

(1 item)

April (2009)

(1 item)

November (2008)

(1 item)

October (2008)

(1 item)

September (2008)

(1 item)

July (2008)

(1 item)

June (2008)

(1 item)

May (2008)

(2 items)

April (2008)

(2 items)

March (2008)

(5 items)

January (2008)

(3 items)

December (2007)

(1 item)

November (2007)

(1 item)

October (2007)

(1 item)

September (2007)

(3 items)

August (2007)

(1 item)

July (2007)

(1 item)

June (2007)

(2 items)

May (2007)

(8 items)

April (2007)

(2 items)

March (2007)

(7 items)

February (2007)

(2 items)

January (2007)

(2 items)

November (2006)

(1 item)

October (2006)

(2 items)

September (2006)

(1 item)

June (2006)

(2 items)

May (2006)

(4 items)

April (2006)

(1 item)

March (2006)

(5 items)

January (2006)

(1 item)

December (2005)

(3 items)

November (2005)

(2 items)

October (2005)

(2 items)

September (2005)

(8 items)

August (2005)

(7 items)

June (2005)

(3 items)

May (2005)

(7 items)

April (2005)

(6 items)

March (2005)

(1 item)

February (2005)

(2 items)

January (2005)

(5 items)

December (2004)

(5 items)

November (2004)

(7 items)

October (2004)

(3 items)

September (2004)

(7 items)

August (2004)

(16 items)

July (2004)

(10 items)

June (2004)

(27 items)

May (2004)

(15 items)

April (2004)

(15 items)

March (2004)

(13 items)

February (2004)

(16 items)

January (2004)

(15 items)

Blog Home

RSS 2.0

Writing

Programming C# 5.0

Programming WPF

Other Sites

Interact Software

Recursion Schemes and Functors

Thursday 20 March, 2014, 08:47 AM

Erik Meijer recently tweeted a link to Patrick Thomson’s post on recursion schemes. (Erik was the driving force behind two of my favourite technologies of the last decade: LINQ and Rx. If you’re interested in programming languages, he’s well worth following on Twitter: @headinthebox.) It was an interesting article, but I felt it had a small issue: it conflates a very useful idea (recursion schemes) with some related but not strictly necessary Haskell-isms: the Functor type class, and fixed points of recursive-defined parameterised types.

I only dabble in Haskell, so it’s possible I’ve got this wrong. I was going to contact the article’s author (Patrick Thomson) directly for clarification, but couldn’t find his email details, so I decided to post this publicly, with the hope of drawing his attention to it via Twitter. I may yet be embarrassed if he points out a fatal flaw in my argument. Ah well.

Recursion Schemes

The idea at the heart of Patrick’s post seems to be this: we should separate the mechanisms for traversing data structures from the way in which we would like to process the data. His example is a data structure representing a simple syntax tree, and a ‘flatten’ method which walks through an expression tree removing parentheses. Initially, this flattening logic is intermingled with the code that walks the tree:

flatten :: Expr -> Expr
flatten (Literal i)     = Literal i
flatten (Paren e)       = flatten e
flatten (Index e i)     = Index (flatten e) (flatten i)
flatten (Call e args)   = Call (flatten e) (map flatten args)
flatten (Unary op arg)  = Unary op (flatten arg)
flatten (Binary l op r) = Binary (flatten l) op (flatten r)

There’s only one line of interest here, and it’s the version of the function that takes a Paren expression. The rest is essentially boilerplate that describes how to walk through his syntax tree data type.

By the end, he has two functions, topDown and bottomUp, which encapsulate two styles of tree traversal. This enables him to separate out the actual logic—flattening of parentheses—into a much simpler function:

flattenTerm :: Term Expr -> Term Expr
flattenTerm (In (Paren e)) = e  -- remove all Parens
flattenTerm other = other       -- do nothing otherwise

It’s very much easier to understand what this does (strips out parentheses, leaving everything else in place) than it was with the previous example, because it expresses only the important logic. To use it, we combine it with one of Patrick’s traversal functions:

flatten :: Term Expr -> Term Expr
flatten = bottomUp flattenTerm

This walks the syntax tree in a bottom-up fashion, passing each node through that flattenTerm function.

Clever Stuff

There are a couple of particularly clever aspects to the way Patrick achieves this. First, his topDown and bottomUp functions don’t know anything about his specific data type. They could work for any recursive data type. Second, he takes advantage of the Haskell compiler’s ability to generate code that can traverse a recursive data type for you; not only can you separate all the structural boilerplate I showed in the first example from the important logic, you don’t even have to write any of that code yourself.

He then goes on to do one more very clever thing: he recursively constructs a parameterised data type which is, in a sense, infinite. This is an excellent party trick, but it is also where I part company from Patrick a little. My view is that the only reason he needs this clever trick is because he’s been forced into it by a shortcoming of how the compiler generates traversal code. An ideal solution would, in my view, enable you to avoid this. But he seems to regard it as front and centre, rather than an unfortunate workaround:

“That these definitions emerged naturally out of fixed-points and functors, two concepts central to Haskell and to functional programming in general, is doubly amazing.”

To show why I disagree with Patrick on this point, I’ll show two things. First, I’ll show how he was effectively forced into the use of fixed-points as a result of a Haskell feature that suffers (in this particular application) from being a little too general. Second, I’ll show that it’s entirely possible to write equivalents of his topDown and bottomUp functions without using either fixed-points or Haskell’s Functor type class, and that the result is significantly simpler. (There is a loss of generality, but as I hope to show, that generality only adds unwanted complexity in this particular case, and cannot be exploited in practice.)

The Path to Functors and Fixed Points

Patrick starts with the excellent goal of not wanting to write or maintain boilerplate code that walks through his tree-like data structure. In most cases, writing this code is a mechanical process, driven entirely by the structure of the data type. It’s tedious to write, and easy to get wrong, and it essentially duplicates information that was already inherent to the data type’s definition. This is exactly the sort of thing that should be automated.

GHC (the most widely used Haskell compiler) has an optional feature that can write this code for you. This isn’t part of any official specification as far as I can tell; it’s an extension that you need to enable with either a command line switch, or a pragma in your source code:

{-# LANGUAGE DeriveFunctor #-}

With that in place, you can write this sort of thing:

data Foo a
  = NoFoos
  | OneFoo a
  | TwoFoos a a
  deriving (Show, Eq, Functor)

This defines a parameterized type. (Given my normal subject matter, I’m guessing most of my readers have a C# background, so if you’re familiar with C# but not Haskell, then firstly, thanks for reading this far, and secondly, that’s sort of like defining a generic type Foo<a>.) This is a slightly pointless sort of a container—it’s only for illustrative purposes here—that can contain either zero, one, or two items of whatever type you choose for the type parameter. For example OneFoo '!' is a Foo Char containing a single character; TwoFoos True False is a Foo Bool containing two Boolean values.

The interesting part is the final line: the deriving keyword tells the compiler that I’d like it to produce some code for me that makes Foo an instance of various type classes. Only a strictly limited set of known classes is supported here, because the compiler only knows how to generate code for certain types. In this case I’m asking it to generate code for the Show class (which enables any Foo to be turned into a string for display purposes), the Eq class (supporting value comparison) and Functor.

That last one is what enables traversal. Any type f that is an instance of the Functor class provides an fmap function with this signature:

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

The general idea is that a Functor is a container, and that fmap lets you apply a function over all of the items in a Functor. For example, a list is a Functor, so I could use fmap to square all the numbers in a list:

*Main> fmap (\x -> x * x) [1..5]
[1,4,9,16,25]

The function is allowed to change the type if it wants, so I might transform a list of numbers to a list of strings (using the show function available on all types that are an instance of the Show class; all numeric types are in that class):

*Main> fmap show [1..5]
["1","2","3","4","5"]

So broadly speaking, a Functor is a container for some particular type of data, and it might contain any number of pieces of data of that type, and we can use fmap to apply a transformation across all of those pieces of data, producing a new container with the same structure as the original, but holding that transformed data.

So what does that mean for our Foo type? We asked the compiler to provide Functor Foo for us by using the deriving keyword, but this just causes the compiler to generate code that looks more or less like this:

instance Functor Foo where
  fmap f NoFoos        = NoFoos
  fmap f (OneFoo a)    = OneFoo (f a)
  fmap f (TwoFoos a b) = TwoFoos (f a) (f b)

So just as I was able to use fmap to square all the numbers in a list I can now use it to square all the numbers in a Foo, as long as the Foo contains numbers (or contains nothing):

*Main> fmap (\x -> x * x) NoFoos
NoFoos
*Main> fmap (\x -> x * x) (OneFoo 2)
OneFoo 4
*Main> fmap (\x -> x * x) (TwoFoos 3 4)
TwoFoos 9 16

Likewise, I can apply the show function to all the items contained in a Foo, just like I did earlier with a list:

*Main> fmap show NoFoos
NoFoos
*Main> fmap show (OneFoo 2)
OneFoo "2"
*Main> fmap show (TwoFoos 3 4)
TwoFoos "3" "4"

So by putting Functor in the deriving list, the compiler generates fmap for our data type. And this is what Patrick takes advantage of—it enables him to avoid writing boilerplate for traversing his syntax tree data type.

However, there’s a problem: the generated fmap is all very well when our container doesn’t really care what it contains, but what if we want a recursive data type? Patrick’s example is a tree-like structure representing expressions—an expression may contain child expressions. Although his type is conceptually simple, it’s large enough to be slightly unwieldy, so I’ll be using a substantially simplified type that can still illustrate the same idea:

data Bar
  = Node Bar Bar
  | Leaf Int
  deriving (Show, Eq)

This lets us build very simple binary trees, where the leaves always contain a single Int. It’s a recursive data structure—for non-leaves, a Bar contains two child Bar items. Now you might reasonably want to process all the elements in such a tree like we’ve been doing already. Here’s a function that squares everything in a Bar.

squareBar :: Bar -> Bar
squareBar (Leaf i) = Leaf (i * i)
squareBar (Node l r) = Node (squareBar l) (squareBar r)

And here it is in use:

*Main> squareBar (Node (Node (Leaf 1) (Leaf 2)) (Leaf 3))
Node (Node (Leaf 1) (Leaf 4)) (Leaf 9)

That’s lovely, but we’re now back in the world of mingling our traversal with our functionality—squareBar is a mixture of code that knows how to traverse a Bar, and code that performs an operation (squaring the numbers). That’s no good, so how about we just add Functor to the list of classes in deriving? But that won’t work—the compiler complains:

Cannot derive well-kinded instance of form `Functor (Bar ...)'
  Class `Functor' expects an argument of kind `* -> *

The basic problem here is that fmap (which any Functor must supply) is able to change the type of the data it works on—as you saw earlier, I can transform a list of numbers to a list of strings. But my Bar type takes no type parameters, so there’s no way to produce a Bar that contains strings. So this is not a type that fmap can work for.

Now we could easily get rid of the error thus:

data Bar a
  = Node (Bar a) (Bar a)
  | Leaf a
  deriving (Show, Eq, Functor)

This works, and I can now write squareBar using the compiler-generated fmap:

squareBar :: (Bar Int) -> (Bar Int)
squareBar = fmap (\x -> x * x)

And this works as expected:

*Main> squareBar (Node (Node (Leaf 1) (Leaf 2)) (Leaf 3))
Node (Node (Leaf 1) (Leaf 4)) (Leaf 9)

However, this doesn’t really solve the problem I want to solve: fmap can only operate on the values stored in the leaves. What if I want to do something to the non-leaf nodes? For example, going back to my original non-parameterized Bar, I could write this:

leftBar :: Bar -> Bar
leftBar (Leaf i) = Leaf i
leftBar (Node l r) = Node (leftBar l) (Leaf 0)

This walks the tree, and, rather arbitrarily, for each non-leaf node it replaces the right-hand child with a leaf with a value of 0. Here it is in action:

*Main> leftBar (Node (Node (Leaf 1) (Leaf 2)) (Leaf 3))
Node (Node (Leaf 1) (Leaf 0)) (Leaf 0)

This is obviously pointless, but the general idea—being able to transform and possibly replace any node rather than just the leaves—is useful. Indeed, that’s exactly what Patrick’s doing in his example: he’s stripping out certain nodes (parentheses) from the syntax tree.

The problem with my parameterized type is that the generated Functor code targets the wrong thing: it lets me transforms the numbers in the leaves, and not the nodes themselves. In some situations the leaf values might be exactly what I want to change, but not here.

And this is where Patrick starts jumping through hoops. Rather than using the type parameter for the value in the leaves as I did, he uses it for the children. Here’s how that would look with my type:

data Bar a
  = Node a a
  | Leaf Int
  deriving (Show, Eq, Functor)

Now this is kind of weird: this type appears to say that non-leaf nodes no longer have to contain two Bar children. The children are of whatever type is supplied as our argument. But we do actually want those to be of type Bar, because this is, after all, supposed to be a simple tree-like recursive data structure. But that’s no longer clear at a glance.

The compiler may be able to do more work for us, but the price is a loss of clarity.

For our type to work as intended, we want the type argument for Bar to be Bar. But we can’t just say Bar Bar, because that second Bar itself needs a type argument. So how about Bar (Bar Bar)? Well again, we’ve got a problem because that last Bar needs a type argument too. So you want a sort of infinite type: Bar (Bar (Bar (Bar …etc))).

Fortunately, Haskell is a sufficiently clever language that you can create such a type. (The resulting infinite type is the “fixed point” Patrick refers to.) It is possible to define some type X such that X is synonymous with Bar X. This implies that Bar X is synonymous with Bar (Bar X) and also Bar (Bar (Bar X)) and so on. This in turn means that if you have a Bar X, then its children in non-leaf nodes are also of type Bar X: we can have the recursive data structure we want.

Patrick achieves this by writing what is effectively a Y combinator in the type system. Here’s something equivalent to what he does (although he calls it Term):

data Mu f = In (f (Mu f))
out :: Mu f -> f (Mu f)  
out (In t) = t

If we then write Mu Bar, that turns out (for slightly brain-melting reasons) to denote a type which has the characteristics I described for “some type X” a few paragraphs ago.

Where does this get us? Well it enables us to use a parameterized definition of Bar in which the children of non-leaf nodes (rather than the leaves) use the type parameter while still being of the same type as their container. This in turn means that the compiler-supplied Functor implementation now works over the nodes rather than the values in the leaves.

However, it’s all now rather inconvenient. Even if you’re able to take the fixed point of an infinitely recursive type definition in your stride, working with trees now becomes a good deal more inconvenient because we have to build everything via the In constructor in order to use the fixed point type. So instead of:

(Node (Node (Leaf 1) (Leaf 2)) (Leaf 3))

we must now write:

(In (Node (In (Node (In (Leaf 1)) (In (Leaf 2)))) (In (Leaf 3))))

These In functions tend to litter our code, as does the related out function when we want to work with the information in our tree. And it’s all because Functor demands that its type argument is itself a parameterized type. And the only reason it requires that is to allow the function we pass to fmap to change the type as part of its transformation. But if you’re still keeping up, you’ll notice that we can’t actually take advantage of that! The whole point of jumping through this fixed point type hoop was to enable our Bar to contain children of type Bar, so in practice, the first argument to fmap will always be (Mu Bar -> Mu Bar). All this complexity arises because of the generality of fmap, generality that we cannot in fact exploit.

A Simpler Approach

Instead of fmap’s too-general signature:

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

all we really need is this:

efmap :: (a -> a) -> a -> a

Or to put that back into the context of our example, when we’re walking a tree, we’re always going to be mapping nodes onto nodes. In my case, that means a Bar is always mapped to a Bar; in Patrick’s example, that means an Expr is always mapped to an Expr. This is always the case in practice for these examples—when using fmap in this way, its two type arguments (a and b) will always refer to the same type.

I’ve called my degenerate fmap efmap, because it think a functor that maps onto the same type as its input is called an endofunctor. However, I’m not totally sure about that—I’ve read in a couple of places that all Haskell functors are technically endofunctors. I don’t understand the arguments that lead to this conclusion, so I’m evidently not yet enlightened, so perhaps this is the wrong term to use here, but I’ll stick with it for now.

We could define our own class for this:

class Endofunctor a where
  efmap :: (a -> a) -> a -> a

This is just a degenerate version of Functor, in which two type arguments have become one. This simplification means that an Endofunctor is not required to be a parameterised type, unlike a Functor. As far as I can tell, Haskell does not define any such class itself. I’m not entirely sure why, which leads me to suspect I’m missing something. But as I’ll show, this does appear to lead to a simpler result.

Of course, Haskell can’t auto-generate an implementation of Endofunctor for me, but it’s easy enough to write one for my Bar type. (I’m reverting to the original non-parameterized version, by the way.)

instance Endofunctor Bar where
  efmap f (Leaf i)   = Leaf i
  efmap f (Node l r) = Node (f l) (f r)

And then, instead of Patrick’s topDown and bottomUp (modified to use my Mu instead of his Term):

topDown, bottomUp :: Functor f => (Mu f -> Mu f) -> Mu f -> Mu f
topDown f  = In <<< fmap (topDown f) <<< out <<< f 
bottomUp f = out >>> fmap (bottomUP f) >>> In >>> f

we have these much simpler versions that don’t need to bother with the wrapping and unwrapping necessitated by the fixed point type:

bottomUp, topDown :: Endofunctor a => (a -> a) -> a -> a
bottomUp fn = efmap (bottomUp fn) >>> fn
topDown fn  = efmap (topDown fn) <<< fn

As with Patrick’s code, this illustrates the duality between bottom-up and top-down by “reversing the arrows” but with more elegance, I believe.

Likewise, the code that performs the transformation I’m actually interested in is free from all this messy Mu/Term, In/out stuff:

leftBarNode :: Bar -> Bar
leftBarNode (Node l r) = Node (leftBarNode l) (Leaf 0)
leftBarNode other = other

And I no longer need to pepper my tree construction with loads of In functions—I can just construct it directly. Here I’m using that leftBarNode with the bottomUp recursion scheme:

*Main> bottomUp leftBarNode (Node (Node (Leaf 1) (Leaf 2)) (Leaf 3))
Node (Node (Leaf 1) (Leaf 0)) (Leaf 0)

Let’s step back and see where this has taken us.

I have been able to encapsulate recursion schemes in separate functions (topDown and bottomUp) just like in Patrick’s solution, and these are expressed in terms of a type class (Endofunctor, effectively a degenerate form of Functor), enabling each individual data type to define its own structure for traversal purposes. This enables the logic of interest to be separated out from the mechanisms of recursive traversal. It was not necessary to invoke any infinitely nested type magic (no type system Y combinator, no fixed points). This removed all of the associated wrapping and unwrapping clutter, and avoided the cognitive overhead of a recursive data type not being self-evidently recursive. I was able to get away from all that by avoiding the Functor class, which wreaked havoc by being too general for the task at hand.

And that’s why I take issue with Patrick’s conclusion:

“The fact that we can express the duality between top-down and bottom-up traversals merely by ‘reversing the arrows’ that determine our code’s flow, all the while retaining generality and type safety, is nothing short of amazing. That these definitions emerged naturally out of fixed-points and functors, two concepts central to Haskell and to functional programming in general, is doubly amazing.”

The first sentence is true for both Patrick’s and my approach. But I think my code demonstrates that these things do not depend on fixed-points, and while they may depend on endofunctors, they do not depend on functors in the specific guise of Haskell’s Functor type class. On the contrary, fixed points were necessary to work around a problem introduced by the use of Functor and they introduced considerable accidental complexity, as well as reducing the clarity of the data type definition. By avoiding Functor, you no longer need fixed-points, and you can still have all the benefits mentioned in that first sentence.

Not Necessarily an Improvement

All of which is not to say that Patrick’s approach is worse than mine. There’s are two serious problems with my alternative.

The first, and most obvious downside of this is that we lose the support for compiler code generation. By using my own Endofunctor class and its associated efmap, I now have to write the tedious, error-prone traversal code myself. And remember, this is where we came in: one of the principle benefits of the approach Patrick shows was getting the compiler to write this code for us.

There’s also the fact that nothing in the world of Haskell knows about this custom Endofunctor class, unlike the extremely widely supported Functor class. So my solution will not play as nicely with the rest of the Haskell world as Patrick’s.

(Both these problems would go away if something like Endofunctor were a standard part of Haskell, and was supported as a code generation target just like Functor. So it’s tempting to say that the real problem here is Functor, but as a mere dabbler in Haskell, I think that’s a significantly stronger conclusion than I’m qualified to draw.)

So the bottom line is that Patrick’s approach is probably worth the pain. But I believe I have shown that the basic idea of recursion schemes is not in fact dependent on either the Functor class or fixed point types.

So my point is not that Patrick’s way of doing this is wrong. My point is that he oversells Functor and fixed points. Fixed points turn out to be a necessary evil imposed by the (in this case) unwanted generality of Functor. It’s still very clever, though.

Copyright © 2002-2024, Interact Software Ltd. Content by Ian Griffiths. Please direct all Web site inquiries to webmaster@interact-sw.co.uk