foldl traverses with State, foldr traverses with anythingfoldl or foldr?Avi Press gave an excellent talk at Scale By the Bay 2023 about difficulties using Haskell at a startup. He mentions that even experienced Haskellers don’t always know how to use fundamental parts of the language. In particular,
even experienced Haskell engineers aren’t always going to know whether to
foldlorfoldr.
In this article I’ll deduce a firm rule that allows you to make the
correct choice. I will stick to the versions of these functions that
operate on lists; their generalization to
Foldable
warrants a separate article. In summary, the answer is
foldl',
never use foldlfoldl' over foldr whenever possiblefor_But why? Let’s see, by examining what these functions do.
We’ll work with the traditional definitions of foldl and foldr,
given below. The implementations in base are more complicated, for
performance reasons, but the reasoning in this article applies to them too.
foldl :: (b -> a -> b) -> b -> [a] -> b
foldl f z [] = z
foldl f z (a : as) = foldl f (f z a) as
foldr :: (a -> b -> b) -> b -> [a] -> b
foldr f z [] = z
foldr f z (a : as) = f a (foldr f z as)Ostensibly, the difference between foldl and foldr is the that
former “associates a binary operation to the left” and the latter
“associates a binary operation to the right”, as follows.
foldl (**) z [x1, x2, ..., xn] ==
(...((z ** x1) ** x2) **...) ** xn
foldr (**) z [x1, x2, ..., xn] ==
x1 ** (x2 ** ... (xn ** z)...)Those are indeed descriptions of the calculated results, but that
distinction is not particularly important. If we only care about the
result then it’s easy enough to convert between foldl and foldr,
as shown below. The important difference is how they calculate the
result; the conversion below does not preserve behaviour. For example,
foldl (-) 0 calculates a sequence of subtractions in constant
space1; foldr (flip (-)) 0 uses O(n) space.
foldl f z == foldr (flip f) z . reverse
foldr f z == foldl (flip f) z . reverseWe will apply our analysis of foldl to its strict counterpart,
foldl', too.
foldl traverses with StateSo what is the precise difference between how the two folds calculate
their results? Consider this: suppose we didn’t have foldl, we only
had
traverse
for
State.
Nonetheless, we could recover foldl! (In fact we only need
traverse_,
a weaker form of traverse, and in these examples we’ll use for_ = flip traverse_ for syntactic convenience.) The example below shows
how. It converts a function that performs for_ (restricted to
State) into a function that performs foldl.
foldlFromForState ::
(forall a b. [b] -> (b -> State a ()) -> State a ()) ->
forall a b.
(a -> b -> a) ->
a ->
[b] ->
a
foldlFromForState for_ f z bs = flip evalState z $ do
for_ bs $ \b -> do
a <- get
put (f a b)
getfoldl and for_ (restricted to State) are equivalentAnd not only can we get foldl from for_ (restricted to State),
we can get for_ (restricted to State) from foldl. They are
equivalent! Importantly, they are equivalent in both result and
performance characteristics.
forStateFromFoldl ::
(forall a b. (a -> b -> a) -> a -> [b] -> a) ->
forall a b.
[b] ->
(b -> State a ()) ->
State a ()
forStateFromFoldl foldl bs f = do
z <- get
put (foldl g z bs)
where
g a b = execState (f b) aThat is to say, having foldl is equivalent to being able to
traverse_ in State. If you have a foldl in your program you may
as well have used traverse_ or for_ with State (or vice versa).
The same analysis works for the strict left fold, foldl', in place
of lazy left fold, foldl. To obtain foldl' from for_ we would
have to change foldlFromForState to use put $! f a b in place of
put (f a b). forStateFromFoldl' would be a version of for_
(restricted to State) that forces its state after every iteration.
foldr traverses with anythingHow does the behaviour of foldr differ? Suppose we didn’t have
foldr, we only had for_ (the general version). Nonetheless, we
could recover foldr. The example below shows how; it converts an
Applicative-polymorphic for_ into foldr.
foldrFromFor ::
(forall b f. Applicative f => [b] -> (b -> f ()) -> f ()) ->
forall a b.
(b -> a -> a) ->
a ->
[b] ->
a
foldrFromFor for_ f z bs =
runEndoApplicative z $ for_ bs $ \b -> mkEndoApplicative (f b)I’ve used the following convenient type definition and functions:
type EndoApplicative a = Const (Endo a)
mkEndoApplicative :: (a -> a) -> EndoApplicative a ()
mkEndoApplicative = Const . Endo
runEndoApplicative :: a -> EndoApplicative a () -> a
runEndoApplicative a (Const (Endo f)) = f afoldr and for_ (the general version) are equivalentAnd not only can we get foldr from for_, we can get for_ from
foldr. They are equivalent. Again, the equivalence is one not only
of result but also of performance characteristics.
forFromFoldr ::
(forall a b. (b -> a -> a) -> a -> [b] -> a) ->
forall b f.
Applicative f =>
[b] ->
(b -> f ()) ->
f ()
forFromFoldr foldr bs f =
foldr (\b rest -> f b *> rest) (pure ()) bsThat is to say, having foldr is equivalent to being able to
traverse_. If you have a foldr in your program you may as well
just have used traverse_ or for_ with an appropriate choice of
Applicative (or vice versa).
What can we do with this new knowledge? Let’s look at the example of
printing all even elements of a list. We can do so using foldr but
the equivalent in terms of for_ (choosing the Applicative to be
IO) is clearer. The “equivalent” in terms of foldl is wrong; it
uses O(n) space (and completely fails on infinite lists).
printEvensFoldr :: [Int] -> IO ()
printEvensFoldr =
foldr
(\i rest -> when (even i) (print i) *> rest)
(pure ())
printEvensFor :: [Int] -> IO ()
printEvensFor is =
for_ is $ \i -> when (even i) (print i)
printEvensFoldl :: [Int] -> IO ()
printEvensFoldl =
foldl
(\rest i -> when (even i) (print i) *> rest)
(pure ())
. reverseAn old riddle challenges us
to write foldl in terms of foldr. Personally I find the riddle
impossible to solve directly and even when I know the answer I can
hardly understand it. With the code above, though, we can solve the
riddle with no further thought. We know how to turn foldr into
for_ and for_ into foldl, so we simply compose.
foldlFromFoldr ::
(forall a b. (b -> a -> a) -> a -> [b] -> a) ->
forall a b.
(a -> b -> a) ->
a ->
[b] ->
a
foldlFromFoldr foldr =
foldlFromForState (forFromFoldr foldr)After purely mechanical simplification (see appendix below) this becomes
foldr (\b rest a -> rest (f a b)) id bs zWe didn’t need to use any brainpower to solve the riddle! The riddle
can also be solved for foldl'. It ends up the same except with a
strict application:
foldr (\b rest a -> rest $! f a b) id bs zfoldl', foldl or foldr?Now we’re ready to resolve the original dilemma. We’ve seen that the
only difference in functionality between foldl and foldr is that
the latter can be used in a wider range of situations. In consequence
we can specify when one should be used in preference to another.
foldlFirstly, regarding the choice between the two left folds, always use
the strict version foldl', not the lazy version foldl. The latter
can cause space leaks when strictness analysis is off; the former
always avoids those space leaks. I’ve never seen a reason to use
foldl.2 This advice is common knowledge in the Haskell community
and not directly the subject of this article but it seems appropriate
to reiterate it.
foldl' in preference to foldrRegarding the choice between left and right fold, our first thought
might have been been to take into account the ostensible distinction
that the former “associates to the left” and the latter “to the
right”. But we are no longer distracted by this mirage. We saw above
that foldl' is equivalent to for_ restricted to (a strict use of)
State, and foldr is equivalent to general for_, so foldl' is a
special case of foldr. According to the Principle of Least
Power you should use
foldl' in preference to foldr when you can, this is, when the
operation you want to perform is to traverse the list with a state
parameter.
for_foldr does not do a different job to foldl': it does a more
general version of the same job. This was not immediately clear,
however; it required careful analysis. The lack of clarity around the
behavior of folds might be an argument for avoiding them and instead
using for_ with an appropriate choice of Applicative. Personally,
I find for_ much clearer than foldr in many cases. The base
implementation
of (!?), below, is a case in point. It is a foldr that simulates
a for_ in a composition of StateT and Either by handwriting the
bind ((>>=)).
(!?) :: [a] -> Int -> Maybe a
xs !? n
| n < 0 = Nothing
| otherwise = foldr (\x r k ->
case k of
0 -> Just x
_ -> r (k-1)) (const Nothing) xs nI find it much clearer written as a literal for_, as below (but it
can’t be, because StateT isn’t in base). The two implementations
should have equal performance when compiled, assuming sufficient
inlining, because for_ for lists in base is implemented in terms
of foldr.
xs !? n =
| n < 0 = Nothing
| otherwise =
fromEither $ do
flip evalStateT n $ do
for_ xs $ \x -> do
get >>= \case
0 -> lift (Left (Just x))
k -> put (k - 1)
Left Nothing
fromEither :: Either a a -> a
fromEither = either id idfor_ imperative?Yes. Although I don’t know how to precisely define “imperative style”
I am confident in saying that the style of (!?) defined with foldr
is functional and the style of (!?) defined with for_ is
imperative. Yet they calculate exactly the same thing in exactly the
same way. In fact, I think the implementation with for_ is both
imperative and clearer. How can that be? Don’t functional
programmers eschew imperative style? Actually, no: I also think that
Haskell is the world’s finest imperative programming language!
What does the algorithm look like in other imperative programming
languages? Below are two implementations in Python. Each shows the
weakness of Python’s support for imperative programming compared to
Haskell. In the first example the scopes of k, ret and x are
limited to no less than the rest of the function, and the break is
implicitly scoped to the closest enclosing for – you don’t get a
choice about that. By contrast, the corresponding Haskell variables
are scoped to their precise range of use, and the break equivalent
is scoped precisely to its enclosing handler, fromEither. The scope
is maintained even across function call boundaries so you can refactor
and abstract. The second Python example is no better; it just trades
a too-large scope of ret for an abstraction-resistant scope of early
return.
I find imperative style programming in Haskell clear to understand and easy to reason about exactly because Haskell’s type system and expression-based nature allows fine-grained effect tracking and precise control of the scopes of values and effects.
Python example avoiding early return:
def lookup(xs, n):
if n < 0: return None
k = n
ret = None
for x in xs:
if k == 0:
ret = x
break
k -= 1
return retPython example with early return:
def lookup(xs, n):
if n < 0: return None
k = n
for x in xs:
if k == 0:
return x
k -= 1
return NoneBy carefully analysing the behaviour of three Haskell folds on lists
we were able to determine when we should use each. We even discovered
that “imperative style” programming in Haskell can be clearer than
“functional style”. In summary, never use foldl, prefer foldl' to
foldr where you can, or maybe just forget them all and use for_
instead.
MonoidsThis article is the culmination of an idea I wrote about years ago:
What is foldr made
of?.
Brent Yorgey wrote a follow-up, foldr is made of
monoids.
One lesson of the present article is that foldr being “made of
monoids” is equivalent to it being “made of applicatives whose result
type we ignore”, because when you have an applicative whose result
type you ignore, that’s equivalent to having a monoid.
There is also a specific Applicative that corresponds directly to
any given Monoid m, that is, Const m, and my earlier blog post
showed that there is a specific Moniod that foldr is “made of”:
Endo a; that’s why we ended up using Const and Endo to define
foldrFromFor. Instead of “foldr traverses with anything” we could
have said “foldr traverses with Const (Endo _)” (but that’s much
less catchy). However, it is worth observing that the following
characterizations are also valid:
foldl foldMaps with Dual (Endo _)”foldr foldMaps with any Monoid”foldl' foldMaps with StrictEndo _”foldr foldMaps with Endo _”(where StrictEndo is a strict version of Endo, which doesn’t seem
to exist anywhere in the Haskell
ecosystem).
The lens library takes advantage of these correspondences in its
definitions of
foldlOf',
foldlOf
and
foldrOf
(although it uses Endo (Endo _) instead of StrictEndo _).
In any case, the slogan “foldl traverses with State, foldr
traverses with anything” seems the most catchy and the easiest to use
as a guide to practice.
Alexis King has a post from 2019 explaining the difference between
foldl and
foldr.
She agrees that one should never use foldl. Regarding the
distinction between foldl' and foldr she writes
When the accumulation function is strict, use foldl’ to consume the list in constant space, since the whole list is going to have to be traversed, anyway. When the accumulation function is lazy in its second argument, use foldr.
Those rules of thumb are hard to apply because they presuppose that
you already have an (“accumulation”) function (which is also a
misnomer: in the case of foldr it doesn’t accumulate). That is, it’s a
rule that you can use if you start with a function, to determine which
fold to use with that function. By contrast, this article presents a
rule that you can use if you start with a problem, to determine which
fold can solve your problem. If your problem is “traverse with (only)
a state”-shaped then the answer is foldl'; if the problem is
“traverse with anything else”-shaped then the answer is foldr(or in
either case you could just use for_).
Yao Li et al. address the choice of folds in Reasoning about the Garden of Forking Paths from the point of view of laziness and demand analysis.
foldMThere is corresponding characterization of foldM: “foldM traverses
with StateT”, as demonstrated by the following, which is a minor
adjustment to the foldl equivalents.
foldMFromForStateT ::
( forall a b m.
Monad m =>
[b] ->
(b -> StateT a m ()) ->
StateT a m ()
) ->
forall a b m.
Monad m =>
(a -> b -> m a) ->
a ->
[b] ->
m a
foldMFromForStateT for_ f z bs = flip evalStateT z $ do
for_ bs $ \b -> do
a <- get
put =<< lift (f a b)
get
forStateTFromFoldM ::
( forall a b m.
Monad m =>
(a -> b -> m a) ->
a ->
[b] ->
m a
) ->
forall a b m.
Monad m =>
[b] ->
(b -> StateT a m ()) ->
StateT a m ()
forStateTFromFoldM foldM bs f = do
z <- get
put =<< lift (foldM g z bs)
where
g a b = execStateT (f b) a(!?) written that way?It would be even clearer to write (!?) as below. Why not just do
that instead, instead of considering foldr and for_? Because when
written in terms of foldr GHC can apply short cut
fusion,
a rewrite rule that leads to an optimization.
0 !? (x:_) = Just x
_ !? [] = Nothing
n !? (_:xs) = (n-1) !? xsThanks to tobz619 for raising this question and suggesting the alternative implementation.
traverse”There’s a running joke in the Haskell world that “it’s always
traverse”, that is, many complicated transformations can be boiled
down to a use of traverse. This article sheds more light on that
phenomenon; foldl, foldl', foldr and foldM are just different
flavours of traverse_.
FoldableThis article only discusses the relationship between foldl and
foldr as functions on lists, not as functions in the Foldable
class; that can of worms deserves an article of its own. However, the
slogan “foldl traverses with State, foldr traverses with
anything” can be seen as specifying a putative law for how the
Foldable versions of these functions should behave. Determining
whether that law holds in practice, and role of the mysterious
foldr', requires further analysis.
He we do the calculation for foldl. The calculation for foldl' is
almost identical. Starting from the original definition of
foldlFromFoldr, after inlining foldlFromForState and
forFromFoldr, we get
foldlFromFoldr ::
(forall a b. (b -> a -> a) -> a -> [b] -> a) ->
forall a b.
(a -> b -> a) ->
a ->
[b] ->
a
foldlFromFoldr foldr f' z bs' =
flip evalState z $ do
for_ bs' $ \b -> do
a <- get
put (f' a b)
get
where
for_ bs f = foldr (\b rest -> f b *> rest) (pure ()) bsThen we can extract the body of for_ as a variable g
flip evalState z $ do
for_ bs' g
get
where
for_ bs f = foldr (\b rest -> f b *> rest) (pure ()) bs
g b = do
a <- get
put (f' a b)Then inline for_
flip evalState z $ do
foldr (\b rest -> g b *> rest) (pure ()) bs
get
where
g b = do
a <- get
put (f a b)Write g in terms of modify
flip evalState z $ do
foldr (\b rest -> g b *> rest) (pure ()) bs
get
where
g b = modify (flip f b)and then inline g
flip evalState z $ do
foldr (\b rest -> modify (flip f b) *> rest) (pure ()) bs
getand use execState rather than evalState with get
flip execState z $ do
foldr (\b rest -> modify (flip f b) *> rest) (pure ()) bsNow we can take advantage of an interesting property of foldr, that
when h . g == id we have the equality
foldr (\a -> f a) z == h . foldr (\a -> g . f a . h) (g z)(I don’t know if this is a free theorem or whether you have to prove
it by induction.) Observing that execState and modify are
inverses we get
flip execState z $ do
modify $
foldr
(\b rest -> execState $ modify (flip f b) *> modify rest)
(execState (pure ()))
bsWe can combine the two modifys to get
flip execState z $ do
modify $
foldr
(\b rest -> execState $ modify (rest . flip f b))
(execState (pure ()))
bsand use that execState . modify == id to get
foldr
(\b rest -> rest . flip f b)
(execState (pure ()))
bs
zwhich is
foldr (\b rest a -> rest (f a b)) id bs zThe same calculation for foldl' yields
foldr (\b rest a -> rest $! f a b) id bs z