Difference between revisions of "Foldl as foldr alternative"

From HaskellWiki
Jump to navigation Jump to search
(Created page with "This page explains how <hask>foldl</hask> can be written using <hask>foldr</hask>. Yes, there is already such a page! This one explains it differently. The...")
 
Line 9: Line 9:
 
</haskell>
 
</haskell>
   
Now the <hask>f</hask> never changes in the recursion. It turns out things will be simpler later if we pull it out:
+
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:
   
 
<haskell>
 
<haskell>
foldl :: (a -> x -> r) -> a -> [x] -> r
+
f :: Ord x => Set x -> x -> Set x
foldl f a list = go a list
+
f a x = insert x a
where
 
go a [] = a
 
go a (x : xs) = go (f a 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 a xs</hask> as <hask>(go a) 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>
foldl :: (a -> x -> r) -> a -> [x] -> r
+
stuff :: Ord x => Set x -> [x] -> Set x
foldl f a list = go2 list a
+
stuff a [] = a
 
stuff a (x:xs) = stuff (f a x) xs
where
 
go2 [] a = a
 
go2 (x : xs) a = go2 xs (f a x)
 
 
</haskell>
 
</haskell>
   
  +
takes all the elements of the list it's given and stuffs them into the <hask>Set</hask> it's given.
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:
 
  +
 
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 :: (a -> x -> r) -> a -> [x] -> r
+
stuffy :: Ord x => [x] -> Set x -> Set x
foldl f a list = go2 list a
+
stuffy [] a = a
 
stuffy (x : xs) a = stuffy xs (f a x)
where
 
  +
</haskell>
go2 [] = \a -> a
 
  +
go2 (x : xs) = \a -> go2 xs (f a x)
 
 
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>
  +
stuffy :: Ord x => [x] -> Set x -> Set x
 
stuffy a [] = \a -> a
 
stuffy (x : xs) = \a -> stuffy xs (f a x)
 
</haskell>
 
</haskell>
   
Line 42: Line 45:
   
 
<haskell>
 
<haskell>
  +
stuffy :: Ord x => [x] -> Set x -> Set x
foldl f a list = go2 list a
 
 
stuffy [] = (\a -> a)
where
 
go2 [] = (\a -> a)
+
stuffy (x : xs) = \a -> (stuffy xs) (f a x)
go2 (x : xs) = \a -> (go2 xs) (f a x)
 
 
</haskell>
 
</haskell>
   
This isn't an academic paper, so we won't mention Graham Hutton's "Tuturial on the Universality and Expressiveness of Fold", but <hask>go2</hask> fits the <hask>foldr</hask> pattern:
+
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:
   
 
<haskell>
 
<haskell>
go2 ys = foldr whatsit (\a -> a) ys
+
stuffy :: Ord x => [x] -> Set x -> Set x
  +
stuffy ys = foldr whatsit (\a -> a) ys
 
where
 
where
 
whatsit x r = \a -> r (f a x)
 
whatsit x r = \a -> r (f a x)
Line 59: Line 62:
   
 
<haskell>
 
<haskell>
foldl f a list = (foldr whatsit (\a -> a) list) a
+
stuffy :: Ord x => [x] -> Set x -> Set x
  +
stuffy list a = (foldr whatsit (\a -> a) list) a
 
where
 
where
 
whatsit x r = \a -> r (f a x)
 
whatsit x r = \a -> r (f a x)
 
</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 that's all she wrote! One way to look at this final expression is that <hask>whatsit</hask> takes an element of the list, a function produced by folding over the rest of the list, and the value 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.
 
  +
  +
<haskell>
  +
stuff :: Ord x => Set a -> [x] -> Set x
  +
stuff a list = (foldr whatsit (\a -> a) list) a
 
where
  +
whatsit x r = \a -> r (f a x)
  +
</haskell>
  +
  +
Now since we do want to be able to use general <hask>foldl</hask> forms, we should gneralize it again:
  +
  +
<haskell>
  +
foldl :: (a -> x -> r) -> a -> [x] -> r
 
foldl f a xs = (foldr whosit (\a -> a) list) a
 
where
 
whosit x r = \a -> r (f a x)
  +
</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.

Revision as of 05:00, 4 September 2014

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, so we don't really have to worry too much about it. For simplicity, then, let's pick one in particular:

f :: Ord x => Set x -> x -> Set x
f a x = insert x a

While we're at it, let's give a name to foldl f: stuff. So

stuff :: Ord x => Set x -> [x] -> Set x
stuff a [] = a
stuff a (x:xs) = stuff (f a x) xs

takes all the elements of the list it's given and stuffs them into the Set it's given.

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 stuff a xs as (stuff a) xs—that is, to see stuff 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 stuff.

stuffy :: Ord x => [x] -> Set x -> Set x
stuffy [] a = a
stuffy (x : xs) a = stuffy xs (f a x)

So now we see that stuffy 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 stuffy just a little:

stuffy :: Ord x => [x] -> Set x -> Set x
stuffy a [] = \a -> a
stuffy (x : xs) = \a -> stuffy xs (f a x)

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

stuffy :: Ord x => [x] -> Set x -> Set x
stuffy [] = (\a -> a)
stuffy (x : xs) = \a -> (stuffy xs) (f a x)

This isn't an academic paper, so we won't mention Graham Hutton's "Tuturial on the Universality and Expressiveness of Fold", but stuffy fits the foldr pattern:

stuffy :: Ord x => [x] -> Set x -> Set x
stuffy ys = foldr whatsit (\a -> a) ys
  where
    whatsit x r = \a -> r (f a x)

Substituting this in,

stuffy :: Ord x => [x] -> Set x -> Set x
stuffy list a = (foldr whatsit (\a -> a) list) a
  where
    whatsit x r = \a -> r (f a x)

And that's just about it! We wanted stuff, however, not stuffy, so let's swap the argument order again:

stuff :: Ord x => Set a -> [x] -> Set x
stuff a list = (foldr whatsit (\a -> a) list) a
  where
    whatsit x r = \a -> r (f a x)

Now since we do want to be able to use general foldl forms, we should gneralize it again:

<haskell> foldl :: (a -> x -> r) -> a -> [x] -> r foldl f a xs = (foldr whosit (\a -> a) list) a

 where
   whosit x r = \a -> r (f a x)

</haskell.

The way to look at this final expression is that whosit takes an element of the list, a function produced by folding f into the rest of the list, and the initial value, a of an accumulator. It applies f to the accumulator it's given and the list element, and passes the result forward to the function it got.