Difference between revisions of "Foldl as foldr"

From HaskellWiki
Jump to navigation Jump to search
(introduction)
 
(7 intermediate revisions by 2 users not shown)
Line 2: Line 2:
 
that both <hask>foldl</hask> and <hask>foldl'</hask> can be expressed as <hask>foldr</hask>.
 
that both <hask>foldl</hask> and <hask>foldl'</hask> can be expressed as <hask>foldr</hask>.
 
(<hask>foldr</hask> may [http://www.willamette.edu/~fruehr/haskell/evolution.html lean so far right] it came back left again.)
 
(<hask>foldr</hask> may [http://www.willamette.edu/~fruehr/haskell/evolution.html lean so far right] it came back left again.)
The converse is not true, since <hask>foldr</hask> may work on infinite lists,
 
which <hask>foldl</hask> variants never can do.
 
 
It holds
 
It holds
 
<haskell>
 
<haskell>
Line 10: Line 8:
 
foldr (\b g x -> g (f x b)) id bs a
 
foldr (\b g x -> g (f x b)) id bs a
 
</haskell>
 
</haskell>
  +
  +
  +
(The converse is not true, since <hask>foldr</hask> may work on infinite lists,
  +
which <hask>foldl</hask> variants never can do. However, for ''finite'' lists, <hask>foldr</hask> ''can'' also be written in terms of <hask>foldl</hask> (although losing laziness in the process), in a similar way like this:
  +
<haskell>
  +
foldr :: (b -> a -> a) -> a -> [b] -> a
  +
foldr f a bs =
  +
foldl (\g b x -> g (f b x)) id bs a
  +
</haskell>
  +
)
   
 
Now the question are:
 
Now the question are:
 
* How can someone find a convolved expression like this?
 
* How can someone find a convolved expression like this?
 
* How can we benefit from this rewrite?
 
* How can we benefit from this rewrite?
  +
  +
  +
== Folding by concatenating updates ==
  +
  +
Instead of thinking in terms of <hask>foldr</hask> and a function <hask>g</hask> 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.
  +
<haskell>
  +
newtype Update a = Update {evalUpdate :: a -> a}
  +
</haskell>
  +
We need a way to assemble several updates.
  +
To this end we define a <hask>Monoid</hask> instance.
  +
<haskell>
  +
instance Monoid (Update a) where
  +
mempty = Update id
  +
mappend (Update x) (Update y) = Update (y.x)
  +
</haskell>
  +
Now left-folding is straight-forward.
  +
<haskell>
  +
foldlMonoid :: (a -> b -> a) -> a -> [b] -> a
  +
foldlMonoid f a bs =
  +
flip evalUpdate a $
  +
mconcat $
  +
map (Update . flip f) bs
  +
</haskell>
  +
Now, where is the <hask>foldr</hask>?
  +
It is hidden in <hask>mconcat</hask>.
  +
<haskell>
  +
mconcat :: Monoid a => [a] -> a
  +
mconcat = foldr mappend mempty
  +
</haskell>
  +
Since <hask>mappend</hask> must be associative
  +
(and is actually associative for our <hask>Update</hask> monoid),
  +
<hask>mconcat</hask> could also be written as <hask>foldl</hask>,
  +
but this is avoided, precisely <hask>foldl</hask> fails on infinite lists.
  +
  +
By the way:
  +
<hask>Update a</hask> is just <hask>Dual (Endo a)</hask>.
  +
If you use a <hask>State</hask> monad instead of a monoid,
  +
you obtain an alternative implementation of <hask>mapAccumL</hask>.
  +
  +
  +
== foldl which may terminate early ==
   
 
The answer to the second question is:
 
The answer to the second question is:
We can write a <hask>foldl</hask> that may stop before reaching the end of the input list
+
Using the <hask>foldr</hask> expression we can write variants of <hask>foldl</hask>
  +
that behave slightly different from the original one.
  +
E.g. we can write a <hask>foldl</hask> that can stop before reaching the end of the input list
 
and thus may also terminate on infinite input.
 
and thus may also terminate on infinite input.
  +
The function <hask>foldlMaybe</hask> terminates with <hask>Nothing</hask> as result
  +
when it encounters a <hask>Nothing</hask> as interim accumulator result.
  +
<haskell>
  +
foldlMaybe :: (a -> b -> Maybe a) -> a -> [b] -> Maybe a
  +
foldlMaybe f a bs =
  +
foldr (\b g x -> f x b >>= g) Just bs a
  +
</haskell>
  +
  +
Maybe the monoidic version is easier to understand.
  +
The implementation of the fold is actually the same, we do only use a different monoid.
  +
<haskell>
  +
import Control.Monad ((>=>), )
  +
  +
newtype UpdateMaybe a = UpdateMaybe {evalUpdateMaybe :: a -> Maybe a}
  +
  +
instance Monoid (UpdateMaybe a) where
  +
mempty = UpdateMaybe Just
  +
mappend (UpdateMaybe x) (UpdateMaybe y) = UpdateMaybe (x>=>y)
  +
  +
foldlMaybeMonoid :: (a -> b -> Maybe a) -> a -> [b] -> Maybe a
  +
foldlMaybeMonoid f a bs =
  +
flip evalUpdateMaybe a $
  +
mconcat $
  +
map (UpdateMaybe . flip f) bs
  +
</haskell>
  +
  +
  +
== Practical example: Parsing numbers using a bound ==
  +
  +
As a practical example consider a function that converts an integer string to an integer,
  +
but that aborts when the number exceeds a given bound.
  +
With this bound it is possible to call <hask>readBounded 1234 $ repeat '1'</hask>
  +
which will terminate with <hask>Nothing</hask>.
  +
<haskell>
  +
readBounded :: Integer -> String -> Maybe Integer
  +
readBounded bound str =
  +
case str of
  +
"" -> Nothing
  +
"0" -> Just 0
  +
_ -> foldr
  +
(\digit addLeastSig mostSig ->
  +
let n = mostSig*10 + toInteger (Char.digitToInt digit)
  +
in guard (Char.isDigit digit) >>
  +
guard (not (mostSig==0 && digit=='0')) >>
  +
guard (n <= bound) >>
  +
addLeastSig n)
  +
Just str 0
  +
  +
readBoundedMonoid :: Integer -> String -> Maybe Integer
  +
readBoundedMonoid bound str =
  +
case str of
  +
"" -> Nothing
  +
"0" -> Just 0
  +
_ ->
  +
let m digit =
  +
UpdateMaybe $ \mostSig ->
  +
let n = mostSig*10 + toInteger (Char.digitToInt digit)
  +
in guard (Char.isDigit digit) >>
  +
guard (not (mostSig==0 && digit=='0')) >>
  +
guard (n <= bound) >>
  +
Just n
  +
in evalUpdateMaybe (mconcat $ map m str) 0
  +
</haskell>
  +
  +
== See also ==
  +
  +
* Graham Hutton: [http://www.cs.nott.ac.uk/~gmh/fold.pdf A tutorial on the universality and expressiveness of fold]
  +
* [[Fold]]
  +
* [[Foldr Foldl Foldl']]
   
 
[[Category:Idioms]]
 
[[Category:Idioms]]

Revision as of 11:01, 21 November 2011

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.) It holds

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


(The converse is not true, since foldr may work on infinite lists, which foldl variants never can do. However, for finite lists, foldr can also be written in terms of foldl (although losing laziness in the process), in a similar way like this:

foldr :: (b -> a -> a) -> a -> [b] -> a
foldr f a bs =
   foldl (\g b x -> g (f b x)) 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: Update a is just Dual (Endo a). 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: Using the foldr expression we can write variants of foldl that behave slightly different from the original one. E.g. we can write a foldl that can 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

Maybe the monoidic version is easier to understand. The implementation of the fold is actually the same, we do only use a different monoid.

import Control.Monad ((>=>), )

newtype UpdateMaybe a = UpdateMaybe {evalUpdateMaybe :: a -> Maybe a}

instance Monoid (UpdateMaybe a) where
   mempty = UpdateMaybe Just
   mappend (UpdateMaybe x) (UpdateMaybe y) = UpdateMaybe (x>=>y)

foldlMaybeMonoid :: (a -> b -> Maybe a) -> a -> [b] -> Maybe a
foldlMaybeMonoid f a bs =
   flip evalUpdateMaybe a $
   mconcat $
   map (UpdateMaybe . flip f) bs


Practical example: Parsing numbers using a bound

As a practical example consider a function that converts an integer string to an integer, but that aborts when the number exceeds a given bound. With this bound it is possible to call readBounded 1234 $ repeat '1' which will terminate with Nothing.

readBounded :: Integer -> String -> Maybe Integer
readBounded bound str =
   case str of
      ""  -> Nothing
      "0" -> Just 0
      _ -> foldr
         (\digit addLeastSig mostSig ->
            let n = mostSig*10 + toInteger (Char.digitToInt digit)
            in  guard (Char.isDigit digit) >>
                guard (not (mostSig==0 && digit=='0')) >>
                guard (n <= bound) >>
                addLeastSig n)
         Just str 0

readBoundedMonoid :: Integer -> String -> Maybe Integer
readBoundedMonoid bound str =
   case str of
      ""  -> Nothing
      "0" -> Just 0
      _ ->
         let m digit =
               UpdateMaybe $ \mostSig ->
                  let n = mostSig*10 + toInteger (Char.digitToInt digit)
                  in  guard (Char.isDigit digit) >>
                      guard (not (mostSig==0 && digit=='0')) >>
                      guard (n <= bound) >>
                      Just n
         in  evalUpdateMaybe (mconcat $ map m str) 0

See also