Difference between revisions of "Foldl as foldr alternative"

From HaskellWiki
Jump to navigation Jump to search
(add a stricter, more general variant for foldlWhile, foldl'Breaking)
 
(10 intermediate revisions by 2 users not shown)
Line 1: Line 1:
 
This page explains how <hask>foldl</hask> can be written using <hask>foldr</hask>. Yes, there is already [[Foldl as foldr|such a page]]! This one explains it differently.
 
This page explains how <hask>foldl</hask> can be written using <hask>foldr</hask>. Yes, there is already [[Foldl as foldr|such a page]]! This one explains it differently.
  +
   
 
The usual definition of <hask>foldl</hask> looks like this:
 
The usual definition of <hask>foldl</hask> looks like this:
Line 11: Line 12:
   
   
Now the <hask>f</hask> never changes in the recursion, so we don't really have to worry too much about it. For simplicity, then, let's pick one in particular:
+
Now the <hask>f</hask> never changes in the recursion. It turns out things will be simpler later if we pull it out:
   
   
 
<haskell>
 
<haskell>
f :: Ord x => Set x -> x -> Set x
+
foldl :: (a -> x -> r) -> a -> [x] -> r
f a x = insert x a
+
foldl f a list = go a list
 
where
  +
go acc [] = acc
 
go acc (x : xs) = go (f acc x) xs
 
</haskell>
 
</haskell>
   
   
 
-----
While we're at it, let's give a name to <hask>foldl f</hask>: <hask>stuff</hask>. So
 
  +
  +
 
For some reason (maybe we're crazy; maybe we want to do weird things with fusion; who knows?) we want to write this using <hask>foldr</hask>. Haskell programmers like curry, so it's natural to see <hask>go acc xs</hask> as <hask>(go acc) xs</hask>&mdash;that is, to see <hask>go a</hask> as a function that takes a list and returns the result of folding <hask>f</hask> into the list starting with an accumulator value of <hask>a</hask>. This perspective, however, is the ''wrong one'' for what we're trying to do here. So let's change the order of the arguments of the helper:
   
   
 
<haskell>
 
<haskell>
stuff :: Ord x => Set x -> [x] -> Set x
+
foldl :: (a -> x -> r) -> a -> [x] -> r
stuff a [] = a
+
foldl f a list = go2 list a
  +
where
stuff a (x:xs) = stuff (f a x) xs
 
  +
go2 [] acc = acc
 
go2 (x : xs) acc = go2 xs (f acc x)
 
</haskell>
 
</haskell>
   
   
 
So now we see that <hask>go2 xs</hask> is a function that takes an accumulator and uses it as the initial value to fold <hask>f</hask> into <hask>xs</hask>. With this shift of perspective, we can rewrite <hask>go2</hask> just a little, shifting its second argument into an explicit lambda:
takes all the elements of the list it's given and stuffs them into the <hask>Set</hask> it's given.
 
   
   
  +
<haskell>
-----
 
 
foldl :: (a -> x -> r) -> a -> [x] -> r
  +
foldl f a list = go2 list a
  +
where
 
go2 [] = \acc -> acc
  +
go2 (x : xs) = \acc -> go2 xs (f acc x)
  +
</haskell>
   
   
 
Believe it or not, we're almost done! How is that? Let's parenthesize a bit for emphasis:
For some reason (maybe we're crazy; maybe we want to do weird things with fusion; who knows?) we want to write this using <hask>foldr</hask>. Haskell programmers like curry, so it's natural to see <hask>stuff a xs</hask> as <hask>(stuff a) xs</hask>&mdash;that is, to see <hask>stuff a</hask> as a function that takes a list and returns the result of folding <hask>f</hask> into the list starting with an accumulator value of <hask>a</hask>. This perspective, however, is the ''wrong one'' for what we're trying to do here. So let's change the order of the arguments of <hask>stuff</hask>.
 
   
   
 
<haskell>
 
<haskell>
  +
foldl f a list = go2 list a
stuffy :: Ord x => [x] -> Set x -> Set x
 
  +
where
stuffy [] a = a
 
  +
go2 [] = (\acc -> acc) -- nil case
stuffy (x : xs) a = stuffy xs (f a x)
 
  +
go2 (x : xs) = \acc -> (go2 xs) (f acc x) -- construct x (go2 xs)
 
</haskell>
 
</haskell>
   
   
 
This isn't an academic paper, so we won't mention Graham Hutton's [https://www.cs.nott.ac.uk/~gmh/fold.pdf "Tutorial on the Universality and Expressiveness of Fold"], but <hask>go2</hask> fits the <hask>foldr</hask> pattern, constructing its result in non-nil case from the list's head element (<hask>x</hask>) and the recursive result for its tail (<hask>go2 xs</hask>):
So now we see that <hask>stuffy xs</hask> is a function that takes an accumulator and uses it as the initial value to fold <hask>f</hask> into <hask>xs</hask>. With this shift of perspective, we can rewrite <hask>stuffy</hask> just a little:
 
   
   
 
<haskell>
 
<haskell>
stuffy :: Ord x => [x] -> Set x -> Set x
+
go2 list = foldr construct (\acc -> acc) list
  +
where
stuffy a [] = \a -> a
 
stuffy (x : xs) = \a -> stuffy xs (f a x)
+
construct x r = \acc -> r (f acc x)
 
</haskell>
 
</haskell>
   
   
 
Substituting this in,
Believe it or not, we're almost done! How is that? Let's parenthesize a bit for emphasis:
 
   
   
 
<haskell>
 
<haskell>
stuffy :: Ord x => [x] -> Set x -> Set x
+
foldl f a list = (foldr construct (\acc -> acc) list) a
  +
where
stuffy [] = (\a -> a)
 
stuffy (x : xs) = \a -> (stuffy xs) (f a x)
+
construct x r = \acc -> r (f acc x)
 
</haskell>
 
</haskell>
   
   
 
And that's all she wrote! One way to look at this final expression is that <hask>construct</hask> takes an element <hask>x</hask> of the list, a function <hask>r</hask> produced by folding over the rest of the list, and the value of an accumulator, <hask>acc</hask>, "from the left". It applies <hask>f</hask> to the accumulator and the list element, and passes the result forward to the function it got "on the right".
This isn't an academic paper, so we won't mention Graham Hutton's "Tuturial on the Universality and Expressiveness of Fold", but <hask>stuffy</hask> fits the <hask>foldr</hask> pattern:
 
  +
  +
  +
Because <hask>r</hask> is the same function as constructed by the <hask>construct</hask> here, calling this e.g. for a list <hask>[x,y,...,z]</hask> scans through the whole list as-if evaluating a nested lambda applied to the initial value of the accumulator,
   
   
 
<haskell>
 
<haskell>
  +
(\acc->
stuffy :: Ord x => [x] -> Set x -> Set x
 
stuffy ys = foldr whatsit (\a -> a) ys
+
(\acc->
  +
(... (\acc-> (\acc -> acc)
where
 
whatsit x r = \a -> r (f a x)
+
(f acc z)) ...)
  +
(f acc y))
  +
(f acc x)) a
 
</haskell>
 
</haskell>
   
  +
which creates the chain of evaluations as in
   
  +
<haskell>
Substituting this in,
 
  +
(\acc -> acc) (f (... (f (f a x) y) ...) z)
  +
</haskell>
  +
  +
  +
which is just what the normal <hask>foldl</hask> would do.
  +
  +
  +
----
  +
  +
  +
The <hask>construct</hask> function could even be made more clever, and inspect the current element in order to decide whether to ''process'' the list ''further'' or not. Thus, such a variant of <hask>foldl</hask> will be able to stop early, and thus process even infinite lists:
   
   
 
<haskell>
 
<haskell>
stuffy :: Ord x => [x] -> Set x -> Set x
+
foldlWhile t f a list = foldr cons (\acc -> acc) list a
stuffy list a = (foldr whatsit (\a -> a) list) a
 
 
where
 
where
whatsit x r = \a -> r (f a x)
+
cons x r = \acc -> if t x then r (f acc x) else acc
 
</haskell>
 
</haskell>
   
   
And that's just about it! We wanted <hask>stuff</hask>, however, not <hask>stuffy</hask>, so let's swap the argument order again:
+
And if we want our <hask>foldl</hask> to decide whether to process or ''skip'' the current element, then it's
   
   
 
<haskell>
 
<haskell>
stuff :: Ord x => Set a -> [x] -> Set x
+
foldlIf t f a list = foldr cons (\acc -> acc) list a
stuff a list = (foldr whatsit (\a -> a) list) a
 
 
where
 
where
whatsit x r = \a -> r (f a x)
+
cons x r = \acc -> if t x then r (f acc x) else r acc
 
</haskell>
 
</haskell>
   
   
  +
(Just for comparison, skipping <hask>foldr</hask> is of course, trivial:)
Now since we do want to be able to use general <hask>foldl</hask> forms, we should gneralize it again:
 
   
   
 
<haskell>
 
<haskell>
foldl :: (a -> x -> r) -> a -> [x] -> r
+
foldrIf t f a list = foldr cons a list
foldl f a xs = (foldr whosit (\a -> a) list) a
 
 
where
 
where
whosit x r = \a -> r (f a x)
+
cons x r | t x = f x r
  +
| otherwise = r
 
</haskell>
 
</haskell>
   
  +
Another variation is (a more strict and more general)
   
  +
<haskell>
The way to look at this final expression is that <hask>whosit</hask> takes an element of the list, a function produced by folding <hask>f</hask> into the rest of the list, and the initial value, <hask>a</hask> of an accumulator. It applies <hask>f</hask> to the accumulator it's given and the list element, and passes the result forward to the function it got.
 
  +
foldl'Breaking break reduced reducer acc list =
 
foldr cons (\acc -> acc) list acc
  +
where
  +
cons x r acc | break acc x = reduced acc x
  +
| otherwise = r $! reducer acc x
  +
</haskell>

Latest revision as of 14:21, 3 January 2018

This page explains how foldl can be written using foldr. Yes, there is already such a page! This one explains it differently.


The usual definition of foldl looks like this:


foldl :: (a -> x -> r) -> a -> [x] -> r
foldl f a [] = a
foldl f a (x : xs) = foldl f (f a x) xs


Now the f never changes in the recursion. It turns out things will be simpler later if we pull it out:


foldl :: (a -> x -> r) -> a -> [x] -> r
foldl f a list = go a list
  where
    go acc [] = acc
    go acc (x : xs) = go (f acc x) xs




For some reason (maybe we're crazy; maybe we want to do weird things with fusion; who knows?) we want to write this using foldr. Haskell programmers like curry, so it's natural to see go acc xs as (go acc) xs—that is, to see go a as a function that takes a list and returns the result of folding f into the list starting with an accumulator value of a. This perspective, however, is the wrong one for what we're trying to do here. So let's change the order of the arguments of the helper:


foldl :: (a -> x -> r) -> a -> [x] -> r
foldl f a list = go2 list a
  where
    go2 [] acc = acc
    go2 (x : xs) acc = go2 xs (f acc x)


So now we see that go2 xs is a function that takes an accumulator and uses it as the initial value to fold f into xs. With this shift of perspective, we can rewrite go2 just a little, shifting its second argument into an explicit lambda:


foldl :: (a -> x -> r) -> a -> [x] -> r
foldl f a list = go2 list a
  where
    go2 [] = \acc -> acc
    go2 (x : xs) = \acc -> go2 xs (f acc x)


Believe it or not, we're almost done! How is that? Let's parenthesize a bit for emphasis:


foldl f a list = go2 list a
  where
    go2 [] = (\acc -> acc)                      -- nil case
    go2 (x : xs) = \acc -> (go2 xs) (f acc x)   -- construct x (go2 xs)


This isn't an academic paper, so we won't mention Graham Hutton's "Tutorial on the Universality and Expressiveness of Fold", but go2 fits the foldr pattern, constructing its result in non-nil case from the list's head element (x) and the recursive result for its tail (go2 xs):


go2 list = foldr construct (\acc -> acc) list
  where
    construct x r = \acc -> r (f acc x)


Substituting this in,


foldl f a list = (foldr construct (\acc -> acc) list) a
  where
    construct x r = \acc -> r (f acc x)


And that's all she wrote! One way to look at this final expression is that construct takes an element x of the list, a function r produced by folding over the rest of the list, and the value of an accumulator, acc, "from the left". It applies f to the accumulator and the list element, and passes the result forward to the function it got "on the right".


Because r is the same function as constructed by the construct here, calling this e.g. for a list [x,y,...,z] scans through the whole list as-if evaluating a nested lambda applied to the initial value of the accumulator,


(\acc-> 
    (\acc-> 
        (... (\acc-> (\acc -> acc)
                      (f acc z)) ...)
        (f acc y))
    (f acc x)) a

which creates the chain of evaluations as in

(\acc -> acc) (f (... (f (f a x) y) ...) z)


which is just what the normal foldl would do.




The construct function could even be made more clever, and inspect the current element in order to decide whether to process the list further or not. Thus, such a variant of foldl will be able to stop early, and thus process even infinite lists:


foldlWhile t f a list = foldr cons (\acc -> acc) list a
  where
    cons x r = \acc -> if t x then r (f acc x) else acc


And if we want our foldl to decide whether to process or skip the current element, then it's


foldlIf t f a list = foldr cons (\acc -> acc) list a
  where
    cons x r = \acc -> if t x then r (f acc x) else r acc


(Just for comparison, skipping foldr is of course, trivial:)


foldrIf t f a list = foldr cons a list
  where
    cons x r | t x = f x r 
             | otherwise = r

Another variation is (a more strict and more general)

foldl'Breaking break reduced reducer acc list = 
    foldr cons (\acc -> acc) list acc 
          where 
          cons x r acc | break acc x = reduced acc x 
                       | otherwise   = r $! reducer acc x