Foldl as foldr

From HaskellWiki
Revision as of 23:04, 16 February 2009 by Lemming (talk | contribs) (foldl using Update monoid)
Jump to navigation Jump to search

When you wonder whether to choose foldl or foldr you may remember, that both foldl and foldl' can be expressed as foldr. (foldr may lean so far right it came back left again.) The converse is not true, since foldr may work on infinite lists, which foldl variants never can do. It holds

foldl :: (a -> b -> a) -> a -> [b] -> a
foldl f a bs =
   foldr (\b g x -> g (f x b)) id bs a

Now the question are:

  • How can someone find a convolved expression like this?
  • How can we benefit from this rewrite?


Folding by concatenating updates

Instead of thinking in terms of foldr and a function g as argument to the accumulator function, I find it easier to imagine a fold as a sequence of updates. An update is a function mapping from an old value to an updated new value.

newtype Update a = Update {evalUpdate :: a -> a}

We need a way to assemble several updates. To this end we define a Monoid instance.

instance Monoid (Update a) where
   mempty = Update id
   mappend (Update x) (Update y) = Update (y.x)

Now left-folding is straight-forward.

foldlMonoid :: (a -> b -> a) -> a -> [b] -> a
foldlMonoid f a bs =
   flip evalUpdate a $
   mconcat $
   map (Update . flip f) bs

Now, where is the foldr? It is hidden in mconcat.

mconcat :: Monoid a => [a] -> a
mconcat = foldr mappend mempty

Since mappend must be associative (and is actually associative for our Update monoid), mconcat could also be written as foldl, but this is avoided, precisely foldl fails on infinite lists.

By the way: If you use a State monad instead of a monoid, you obtain an alternative implementation of mapAccumL.


foldl which may terminate early

The answer to the second question is: We can write a foldl that may stop before reaching the end of the input list and thus may also terminate on infinite input. The function foldlMaybe terminates with Nothing as result when it encounters a Nothing as interim accumulator result.

foldlMaybe :: (a -> b -> Maybe a) -> a -> [b] -> Maybe a
foldlMaybe f a bs =
   foldr (\b g x -> f x b >>= g) Just bs a