What constitutes a fold for types other than list?

A Fold for Every Occasion

We can actually come up with a generic notion of folding which can apply to a whole bunch of different types. That is, we can systematically define a fold function for lists, trees and more.

This generic notion of fold corresponds to the catamorphisms @pelotom mentioned in his comment.

Recursive Types

The key insight is that these fold functions are defined over recursive types. In particular:

data List a = Cons a (List a) | Nil
data Tree a = Branch (Tree a) (Tree a) | Leaf a

Both of these types are clearly recursive--List in the Cons case and Tree in the Branch case.

Fixed Points

Just like functions, we can rewrite these types using fixed points. Remember the definition of fix:

fix f = f (fix f)

We can actually write something very similar for types, except that it has to have an extra constructor wrapper:

newtype Fix f = Roll (f (Fix f))

Just like fix defines the fixed point of a function, this defines the fixed point of a functor. We can express all our recursive types using this new Fix type.

This allows us to rewrite List types as follows:

data ListContainer a rest = Cons a rest | Nil
type List a = Fix (ListContainer a)

Essentially, Fix allows us to nest ListContainers to arbitrary depths. So we could have:

Roll Nil
Roll (Cons 1 (Roll Nil))
Roll (Cons 1 (Roll (Cons 2 (Roll Nil))))

which correspond to [], [1] and [1,2] respectively.

Seeing that ListContainer is a Functor is easy:

instance Functor (ListContainer a) where
  fmap f (Cons a rest) = Cons a (f rest)
  fmap f Nil           = Nil

I think the mapping from ListContainer to List is pretty natural: instead of recursing explicitly, we make the recursive part a variable. Then we just use Fix to fill that variable in as appropriate.

We can write an analogous type for Tree as well.

"Unwrapping" Fixed Points

So why do we care? We can define fold for arbitrary types written using Fix. In particular:

fold :: Functor f => (f a -> a) -> (Fix f -> a)
fold h = h . fmap (fold h) . unRoll
  where unRoll (Roll a) = a

Essentially, all a fold does is unwrap the "rolled" type one layer at a time, applying a function to the result each time. This "unrolling" lets us define a fold for any recursive type and neatly and naturally generalize the concept.

For the list example, it works like this:

  1. At each step, we unwrap the Roll to get either a Cons or a Nil
  2. We recurse over the rest of the list using fmap.
    1. In the Nil case, fmap (fold h) Nil = Nil, so we just return Nil.
    2. In the Cons case, the fmap just continues the fold over the rest of the list.
  3. In the end, we get a bunch of nested calls to fold ending in a Nil--just like the standard foldr.

Comparing Types

Now lets look at the types of the two fold functions. First, foldr:

foldr :: (a -> b -> b) -> b -> [a] -> b

Now, fold specialized to ListContainer:

fold :: (ListContainer a b -> b) -> (Fix (ListContainer a) -> b)

At first, these look completely different. However, with a bit of massaging, we can show they're the same. The first two arguments to foldr are a -> b -> b and b. We have a function and a constant. We can think of b as () -> b. Now we have two functions _ -> b where _ is () and a -> b. To make life simpler, let's curry the second function giving us (a, b) -> b. Now we can write them as a single function using Either:

Either (a, b) () -> b

This is true because given f :: a -> c and g :: b -> c, we can always write the following:

h :: Either a b -> c
h (Left a) = f a
h (Right b) = g b

So now we can view foldr as:

foldr :: (Either (a, b) () -> b) -> ([a] -> b)

(We are always free to add parentheses around -> like this as long as they're right-associative.)

Now lets look at ListContainer. This type has two cases: Nil, which carries no information and Cons, which has both an a and a b. Put another way, Nil is like () and Cons is like (a, b), so we can write:

type ListContainer a rest = Either (a, rest) ()

Clearly this is the same as what I used in foldr above. So now we have:

foldr :: (Either (a, b) () -> b) -> ([a] -> b)
fold  :: (Either (a, b) () -> b) -> (List a -> b)

So, in fact, the types are isomorphic--just different ways of writing the same thing! I think that's pretty cool.

(As a side note, if you want to know more about this sort of reasoning with types, check out The Algebra of Algebraic Data Types, a nice series of blog posts about just this.)

Back to Trees

So, we've seen how we can define a generic fold for types written as fixed points. We've also seen how this corresponds directly to foldr for lists. Now lets look at your second example, the binary tree. We have the type:

data Tree a = Branch a (Tree a) (Tree a) | Leaf a

we can rewrite this using Fix by following the rules I did above: we replace the recursive part with a type variable:

data TreeContainer a rest = Branch rest rest | Leaf a
type Tree a = Fix (TreeContainer a)

Now we have a tree fold:

fold :: (TreeContainer a b -> b) -> (Tree a -> b)

Your original foldTree looks like this:

foldTree :: (b -> b -> b) -> (a -> b) -> Tree a -> b

foldTree accepts two functions; we'll combine the into one by first currying and then using Either:

foldTree :: (Either (b, b) a -> b) -> (Tree a -> b)

We can also see how Either (b, b) a is isomorphic to TreeContainer a b. Tree container has two cases: Branch, containing two bs and Leaf, containing one a.

So these fold types are isomorphic in the same way as the list example.

Generalizing

There is a clear pattern emerging. Given a normal recursive data type, we can systematically create a non-recursive version of the type, which lets us express the type as a fixed point of a functor. This means that we can mechanically come up with fold functions for all these different types--in fact, we could probably automate the entire process using GHC Generics or something like that.

In a sense, this means that we do not really have different fold functions for different types. Rather, we have a single fold function which is very polymorphic.

More

I first fully understood these ideas from a talk given by Conal Elliott. This goes into more detail and also talks about unfold, which is the dual to fold.

If you want to delve into this sort of thing even more deeply, read the fantastic "Functional Programming with Bananas, Lenses, Envelopes and Barbed Wire" paper. Among other things, this introduces the notions of "catamorphisms" and "anamorphisms" which correspond to folds and unfolds.

Algebras (and Coalgebras)

Also, I can't resist adding a plug for myself :P. You can see some interesting similarities between the way we use Either here and the way I used it when talking about algebras in another SO answer.

There is in fact a deep connection between fold and algebras; moreover, unfold--the aforementioned dual of fold--is connected to coalgebras, which are the dual of algebras. The important idea is that algebraic data types correspond to "initial algebras" which also define folds as outlined in the rest of my answer.

You can see this connection in the general type of fold:

fold :: Functor f => (f a -> a) -> (Fix f -> a)

The f a -> a term looks very familiar! Remember that an f-algebra was defined as something like:

class Functor f => Algebra f a where
  op :: f a -> a

So we can think of fold as just:

fold :: Algebra f a => Fix f -> a

Essentially, fold just lets us "summarize" structures defined using the algebra.


Tikhon's got the technical stuff down. I think I'll try to simplify down from what he said.

The term "folding" has, unfortunately, become ambiguous over the years to mean one of two things:

  1. Reducing a collection sequentially in some order. In Haskell, this is what "folding" means in the Foldable class, which larsmans brings up.
  2. The notion you asked for: "destructing" (opposite of constructing), "observing" or "eliminating" an algebraic data type according to its structure. Also called a catamorphism.

It is possible to define both of these notions generically so that one parametrized function is capable of doing it for a variety of types. Tikhon shows how to do in the second case.

But most often going the whole way with Fix and the algebras and such is overkill. Let's work out a simpler way of writing the fold for any algebraic data type. We'll use Maybe, pairs, lists and trees as our examples:

data Maybe a = Nothing | Just a
data Pair a b = Pair a b
data List a = Nil | Cons a (List a)
data Tree x = Leaf x | Branch (Tree x) (Tree x)
data BTree a = Empty | Node a (BTree a) (BTree a)

Note that Pair is not recursive; the procedure I'm going to show doesn't assume that the "fold" type is recursive. People don't usually call this case a "fold," but it's really the non-recursive case of the same concept.

First step: the fold for a given type will consume the folded type and produce some parameter type as its result. I like to call the latter r (for "result"). So:

foldMaybe :: ... -> Maybe a -> r
foldPair  :: ... -> Pair a b -> r
foldList  :: ... -> List a -> r
foldTree  :: ... -> Tree a -> r
foldBTree :: ... -> BTree a -> r

Second step: in addition to the last argument (the one for the structure), the fold takes as many arguments as the type has constructors. Pair has one constructor and our other examples have two, so:

foldMaybe :: nothing -> just -> Maybe a -> r
foldPair  :: pair -> Pair a b -> r 
foldList  :: nil -> cons -> List a -> r
foldTree  :: leaf -> branch -> Tree a -> r
foldBTree :: empty -> node -> BTree a -> r

Third step: each of these arguments has the same arity as the constructor it corresponds to. Let's treat the constructors as functions, and write out their types (making sure the type variables match up with the ones in the signatures we're writing):

Nothing :: Maybe a
Just    :: a -> Maybe a

Pair    :: a -> b -> Pair a b

Nil     :: List a
Cons    :: a -> List a -> List a

Leaf    :: a -> Tree a
Branch  :: Tree a -> Tree a -> Tree a

Empty   :: BTree a
Node    :: a -> BTree a -> BTree a -> BTree a

Step 4: in the signature of each constructor, we will replace all occurrences of the data type it constructs with our type variable r (that we're using in our fold signatures):

nothing := r
just    := a -> r

pair    := a -> b -> r

nil     := r
cons    := a -> r -> r

leaf    := a -> r
branch  := r -> r -> r

empty   := r
node    := a -> r -> r -> r

As you can see, I've "assigned" the resulting signatures to my dummy type variables from the second step. Now Step 5: fill those in into the earlier sketch fold signatures:

foldMaybe :: r -> (a -> r) -> Maybe a -> r
foldPair  :: (a -> b -> r) -> Pair a b -> r 
foldList  :: r -> (a -> r -> r) -> List a -> r
foldTree  :: (a -> r) -> (r -> r -> r) -> Tree a -> r
foldBTree :: r -> (a -> r -> r -> r) -> BTree a -> r

Now, these are signatures for the folds of those types. They have a funny argument order, because I did this mechanically by reading the fold type off the data declarations and constructor types, but for some reason in functional programming it's conventional to put base cases first in data definitions yet recursive case handlers first in fold definitions. No problem! Let's reshuffle them to make them more conventional:

foldMaybe :: (a -> r) -> r -> Maybe a -> r
foldPair  :: (a -> b -> r) -> Pair a b -> r 
foldList  :: (a -> r -> r) -> r -> List a -> r
foldTree  :: (r -> r -> r) -> (a -> r) -> Tree a -> r
foldBTree :: (a -> r -> r -> r) -> r -> BTree a -> r

The definitions can also be filled in mechanically. Let's pick foldBTree and implement it step by step. The fold for a given type is the one function of the type we figured out that meets this condition: folding with the type's constructors is an identity function over that type (you get the same result as the value you started with).

We'll start like this:

foldBTree :: (a -> r -> r -> r) -> r -> BTree a -> r
foldBTree = ???

We know it takes three arguments, so we can add variables to reflect them. I'll use long descriptive names:

foldBTree :: (a -> r -> r -> r) -> r -> BTree a -> r
foldBTree branch empty tree = ???

Looking at the data declaration, we know BTree has two possible constructors. We can split the definition into a case for each, and fill out variables for their elements:

foldBTree :: (a -> r -> r -> r) -> r -> BTree a -> r
foldBTree branch empty Empty = ???
foldBTree branch empty (Branch a l r) = ???
    -- Let's use comments to keep track of the types:
    -- a :: a
    -- l, r :: BTree a

Now, short of something like undefined, the only way to fill in the first equation is with empty:

foldBTree :: (a -> r -> r -> r) -> r -> BTree a -> r
foldBTree branch empty Empty = empty
foldBTree branch empty (Branch a l r) = ???
    -- a :: a
    -- l, r :: BTree a

How do we fill in the second equation? Again, short of undefined, we have this:

branch :: a -> r -> r -> r
a      :: a
l, r   :: BTree a

If we had subfold :: BTree a -> r, we could do branch a (subfold l) (subfold r) :: r. But of course, we can write 'subfold' easily:

foldBTree :: (a -> r -> r -> r) -> r -> BTree a -> r
foldBTree branch empty Empty = empty
foldBTree branch empty (Branch a l r) = branch a (subfold l) (subfold r)
    where subfold = foldBTree branch empty

This is the fold for BTree, because foldBTree Branch Empty anyTree == anyTree. Note that foldBTree isn't the only function of this type; there's also this:

mangleBTree :: (a -> r -> r -> r) -> r -> BTree a -> r
mangleBTree branch empty Empty = empty
mangleBTree branch empty (Branch a l r) = branch a (submangle r) (submangle l)
    where submangle = mangleBTree branch empty

But in general, mangleBTree doesn't have the required property; for example if we have foo = Branch 1 (Branch 2 Empty Empty) Empty, it follows that mangleBTree Branch Empty foo /= foo. So mangleBTree, though it has the correct type, is not the fold.


Now, let's take a step back from details, and concentrate on that last point with the mangleTree example. A fold (in the structural sense, #2 at the top of my answer) is nothing more and nothing else than the simplest, non-trivial function for an algebraic type such that, when you give pass in the type's constructors as its arguments, it becomes the identity function for that type. (By nontrivial I mean that things like foo f z xs = xs is not allowed.)

This is very significant. Two ways I like to think about it are as follows:

  1. The fold for a given type can "see" all the information contained by any value of that type. (This is why it's able to perfectly "reconstruct" any value of that type from the ground up using the type's constructors.)
  2. The fold is the most general "consumer" function for that type. Any function that consumes a value of the type in question can be written so that the only operations it uses from that type are the fold and the constructors. (Though the fold-only versions of some functions are hard to write and perform badly; try writing tail :: [a] -> [a] with foldr, (:) and [] as a painful exercise.)

And the second point goes even further, in that you don't even need the constructors. You can implement any algebraic type without using data declarations or constructors, using nothing but folds:

{-# LANGUAGE RankNTypes #-}

-- | A Church-encoded list is a function that takes the two 'foldr' arguments
-- and produces a result from them.
newtype ChurchList a = 
    ChurchList { runList :: forall r. 
                            (a -> r -> r)  -- ^ first arg of 'foldr'
                         -> r              -- ^ second arg of 'foldr'
                         -> r              -- ^ 'foldr' result
               }

-- | Convenience function: make a ChurchList out of a regular list
toChurchList :: [a] -> ChurchList a
toChurchList xs = ChurchList (\kons knil -> foldr kons knil xs)

-- | 'toChurchList' isn't actually needed, however, we can make do without '[]'
-- completely.
cons :: a -> ChurchList a -> ChurchList a
cons x xs = ChurchList (\f z -> f x (runlist xs f z))

nil :: ChurchList a
nil = ChurchList (\f z -> z)

foldr' :: (a -> r -> r) -> r -> ChurchList a -> r
foldr' f z xs = runList xs f z

head :: ChurchList a -> Maybe a
head = foldr' ((Just .) . const) Nothing

append :: ChurchList a -> ChurchList a -> ChurchList a
append xs ys = foldr' cons ys xs

-- | Convert a 'ChurchList' to a regular list.
fromChurchList :: ChurchList a -> [a]
fromChurchList xs = runList xs (:) []

As an exercise you can try writing other types in this way (which uses the RankNTypes extension—read this for a primer). This technique is called Church encoding, and is sometimes useful in actual programming—for example, GHC uses something called foldr/build fusion to optimize list code to remove intermediate lists; see this Haskell Wiki page, and note the type of build:

build :: (forall b. (a -> b -> b) -> b -> b) -> [a]
build g = g (:) []

Except for the newtype, this is the same as my fromChurchList above. Basically, one of the rules that GHC uses to optimize list processing code is this:

-- Don't materialize the list if all we're going to do with it is
-- fold it right away:
foldr kons knil (fromChurchList xs) ==> runChurchList xs kons knil

By implementing the basic list functions to use Church encodings internally, inlining their definitions aggressively, and applying this rule to the inlined code, nested uses of functions like map can be fused into a tight loop.