Re: [Haskell-cafe] Re: Definition of tail recursive wrt Folds

2009-03-28 Thread Bertram Felgenhauer
Ben Franksen wrote:
 Mark Spezzano wrote:
  Just looking at the definitions for foldr and foldl I see that foldl is
  (apparently) tail recursive while foldr is not.
  
  Why?
  
  Is it because foldl defers calling itself until last whereas foldr
  evaluates itself as it runs?
  
  What, strictly speaking, is the definition of ”tail recursive” as opposed
  to just “recursive”?
 
 An application of some function f inside another function g is in 'tail
 position' (or a 'tail call') if the result of applying f is the result of
 g. Operationally speaking, calling f is the very last thing g does. Tail
 calls can be optimized by a compiler (or interpreter) so that the call does
 not use additional stack; that is, the call can be replaced by a jump.
 
 A function is called ”tail recursive” (as opposed to just “recursive”) if
 the recursive call to itself is in tail position. If the compiler performs
 tail call optimization, tail recursive functions can work with constant
 stack space, similar to a (imperative) loop.
 
 Looking at a definition of foldl, e.g.
 
 foldl f z0 xs0 = lgo z0 xs0 where
   lgo z [] =  z
   lgo z (x:xs) = lgo (f z x) xs
 
 you see that lgo calls itself in tail position, thus is tail recursive. In
 contrast, foldr can be defined as
 
 foldr k z xs = go xs where
   go [] = z
   go (y:ys) = y `k` go ys
 
 where you see that the result of go is not the recursive call to go.
 Instead, the result is  y `k` go ys . Thus, foldr is not tail recursive.
 
 So, if you are saying that foldl defers calling itself until last whereas
 foldr evaluates itself as it runs then you got the right idea, I think.
 The point is that foldr still needs to do something (namely to apply  (y
 `k`)) to the result of applying itself. It needs to remember to do so, and
 thus the stack grows linearly with the size of the list.

Sorry, but that's wrong. It would be right in a strict language. In Haskell,
the 'go ys' term is not evaluated straight away; it is instead turned into
a suspended evaluation (a thunk) that is typically stored on the heap.

The following discussion is implementation specific, with ghc in mind.
Haskell itself has no notion of a stack.

In fact both using foldl and using foldr can produce stack overflows:

  Prelude foldl (+) 0 [1..10^7]
  *** Exception: stack overflow
  Prelude foldr (+) 0 [1..10^7]
  *** Exception: stack overflow

Let's examine why. First, consider the foldl case. For simplicity, I'll
ignore the evaluation of [1..10^7]. The first few evaluation steps are

 foldl (+) 0 [1,2,3..100]
  - lgo 0 [1,2,3..100]
  - lgo (0+1) [2,3,4..100]
  - lgo ((0+1)+2) [3,4,5..10]

None of these steps uses the stack - foldl is indeed tail recursive. However,
the ((0+1)+2) is a thunk on the heap. Continuing,

  - lgo ((...(0+1)+...)+999) [1000]
  - lgo ((...(0+1)+...)+1000) []
  - ((...(0+1)+...)+1000)

Now we have to evaluate that huge thunk. This turns out to cause trouble
because + (for Integers) is strict. So in order to find x+1000, the
code needs the value of x first. And that's where the stack gets
involved: the information of the pending addition, (?+1000) is pushed
onto the stack, and evaluation proceeds with the first term.

Denoting the stack by [[item1, item2, ...]], evaluation continues like
this:

  - [[(?+1000)]] ((...(0+1)+...)+999)
  - [[(?+1000),(?+999)]]

The stack will keep growing, until the (0+1) is reached, or the stack
overflows.

To make things more confusing, ghc has a strictness analyzer that
sometimes manages to avoid such a thunk being built up. For an
example how strictness helps see foldl' (below).


Now for the foldr case. Evaluation in that case looks a bit different:

 foldr (+) 0 [1,2,3..1000]
  - go [1,2,3..1000]
  - 1 + go [2,3,4..1000]

No stack was used so far; the go [2,3,4..100] is a thunk. Now, as
above, we need to add two numbers. And that's where the stack gets
involved again:

  - [[(1+?)]] go [2,3,4..1000]
  - [[(1+?)]] 2 + go [3,4,5..1000]
  - [[(1+?),(2+?)]] go [3,4,5..1000]
  - [[(1+?),(2+?),(3+?)]] go [4,5,6..1000]

and so on, until we reach  go []  or the stack overflows. Note that
there is no reference to 'go' on the stack at all.

If instead of (+), we had a lazy function like (:), the stack would
not get involved in this way:

 foldr (:) [] [1,2,3..1000]
  - go [1,2,3..1000]
  - 1 : go [2,3,4..1000]

Which is in weak head normal form, so evaluation stops here. Later,
when other code examines the list, the 'go [2,3,4..1000]' thunk
will get evaluated.


As a final note, the stack overflow with  foldl  above is cured by using
foldl', which is _strict_ in the accumulator.

For reference,
foldl' f z0 xs0 = lgo z0 xs0
where lgo z [] = z
  lgo z (x:xs) = let z' = f z x in z' `seq` lgo z' xs

 foldl' (+) 0 [1,2,3..100]
  - lgo 0 [1,2,3..100]
  - let z' = 0+1 in z' `seq` lgo z' [2,3,4..100]

Now 

[Haskell-cafe] Re: Definition of tail recursive wrt Folds

2009-03-27 Thread Ben Franksen
Mark Spezzano wrote:
 Just looking at the definitions for foldr and foldl I see that foldl is
 (apparently) tail recursive while foldr is not.
 
 Why?
 
 Is it because foldl defers calling itself until last whereas foldr
 evaluates itself as it runs?
 
 What, strictly speaking, is the definition of ”tail recursive” as opposed
 to just “recursive”?

An application of some function f inside another function g is in 'tail
position' (or a 'tail call') if the result of applying f is the result of
g. Operationally speaking, calling f is the very last thing g does. Tail
calls can be optimized by a compiler (or interpreter) so that the call does
not use additional stack; that is, the call can be replaced by a jump.

A function is called ”tail recursive” (as opposed to just “recursive”) if
the recursive call to itself is in tail position. If the compiler performs
tail call optimization, tail recursive functions can work with constant
stack space, similar to a (imperative) loop.

Looking at a definition of foldl, e.g.

foldl f z0 xs0 = lgo z0 xs0 where
  lgo z [] =  z
  lgo z (x:xs) = lgo (f z x) xs

you see that lgo calls itself in tail position, thus is tail recursive. In
contrast, foldr can be defined as

foldr k z xs = go xs where
  go [] = z
  go (y:ys) = y `k` go ys

where you see that the result of go is not the recursive call to go.
Instead, the result is  y `k` go ys . Thus, foldr is not tail recursive.

So, if you are saying that foldl defers calling itself until last whereas
foldr evaluates itself as it runs then you got the right idea, I think.
The point is that foldr still needs to do something (namely to apply  (y
`k`)) to the result of applying itself. It needs to remember to do so, and
thus the stack grows linearly with the size of the list.

Cheers
Ben

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe