[Haskell-cafe] Tail recursive

Daniel Fischer daniel.is.fischer at googlemail.com
Wed Dec 19 18:18:38 CET 2012


On Mittwoch, 19. Dezember 2012, 17:17:19, J.W. Krol wrote:
> From: jkrzzz at live.com
> To: haskell-cafe at haskell.org
> Subject: Tail recursive
> Date: Wed, 19 Dec 2012 17:07:14 +0100
> 
> Hello,
> I need a non tail recursive version of scanl,

scanl isn't tail recursive, I believe you meant you need a tail recursive 
version. But you probably don't.

scanl produces its result incrementally, if it is consumed sequentially (with 
the consumption forcing complete evaluation of the value), each list element 
is evaluated before the next list cells are created, thus no big thunks are 
built.

However, your code below doesn't produce the same result as scanl.
What it produces is

scanl' f q ls = scanr f q (reverse ls)

or

scanl' f q ls = reverse $ scanl (flip f) q ls

reverse is a bad consumer for scanl results, and scanr can have a stack 
overflow problem because it builds its result from the end of the list 
backward to the front. That works well if the function argument is lazy in its 
second argument, but not if it's strict in that - just like foldr.

> to produce a large enough list
> of >100K vectors (vectors defined as a list) I have following code:

> scanl'::(a -> a -> a) -> a -> [a] -> [a]
> scanl' f q ls      = scanl'' ls (q:[])
>   where
>     scanl'' (x:xs) ys = let
>         h   = head ys
>         x'  = f x h
>         ys' = x':ys	
>      in h `seq` x' `seq` ys' `seq` scanl'' xs ys'
>     scanl'' [] ys = ys

The `seq` on ys' does nothing. seq evaluates its first argument to weak head 
normal form (that is, the outermost constructor is determined, for non-
function types) if its result is demanded, but ys' is already in WHNF.

Looking at your use below, your problem is that h and x' are also only 
evaluated to WHNF, which for the case of lists means that it is determined 
whether they are empty or not. Elements of the list are only evaluated if that 
is necessary to determine whether it is empty.

>     If I call this function as below I still
> got stack-overflow error: head (scanl' (zipWith (+)) ([0,0]) (take 100000
> (repeat [0,1])))

I think the above is only for demonstrative purposes, but

head $ scanl' f q ls

is (with slightly different `seq` behaviour) just

foldl' f q ls

Anyway, your problem is that the `seq`s do not force any of the additions. If 
we look at the first few evaluation steps, we find

scanl'' ([0,1]:xs) [[0,0]]
~> let h = head [[0,0]]
       x' = zipWith (+) [0,1] h
       ys' = x':[[0,0]]
   in h `seq` x' `seq` ys' `seq` scanl'' xs ys'

the initial list is completely evaluated from the start, so the (h `seq`) 
doesn't do anything here. The (x' `seq`) forces

zipWith (+) [0,1] [0,0]

into weak head normal form, giving

(0 + 0) : zipWith (+) [1] [0]

Thus, the next round of scanl'' goes

scanl'' ([0,1]:xs) (((0+0) : zipWith (+) [1] [0]) : [0,0] : [])

Once again, the head of the ys argument is already in WHNF (it was forced in 
the previous round), and the only seq that has any effect is the (x' `seq`), 
which forces

zipWith (+) [0,1] ((0+0) : zipWith (+) [1] [0])

into

(0 + (0+0)) : zipWith (+) [1] (zipWith (+) [1] [0])

When that is continued, lists containing ever larger thunks of the form

(0 + (...  + (0 + 0)...))

respectively

zipWith (+) [1] (zipWith (+) [1] (...(zipWith (+) [1] [0])...))

are built.

To avoid that, you could use deepseq from the Control.DeepSeq module in the 
deepseq package instead of seq (and you only need to deepseq x').

But that's a bit of a sledge hammer, depending on your application, something 
less drastic and more efficient could be possible.

> 
> What do I wrong. I am not an experienced Haskell programmer, but find the
> behavior quite unexplainable. Thank for your answer.
> RegardsJacq



More information about the Haskell-Cafe mailing list