Lazy evaluation and tail-recursion
 
            Hello, A question recently popped into my mind: does lazy evaluation reduce the need to "proper" tail-recursion? I mean, for instance : fmap f [] = [] fmap f (x:xs) = f x : fmap f xs Here fmap is not tail-recursive, but thanks to the fact that operator (:) is lazy, I think that it may still run in constant space/time, am I right?
 
            Hi, Yves Parès wrote:
A question recently popped into my mind: does lazy evaluation reduce the need to "proper" tail-recursion? I mean, for instance :
fmap f [] = [] fmap f (x:xs) = f x : fmap f xs
Here fmap is not tail-recursive, but thanks to the fact that operator (:) is lazy, I think that it may still run in constant space/time, am I right?
In a sense, that definition of fmap is tail-recursive. To see that, consider how a non-strict list could be encoded in a strict language: data EvaluatedList a = Cons a (List a) | Empty type List a = () -> EvaluatedList a map :: (a -> b) -> (List a -> List b) map f xs = \_ -> case xs () of Cons x xs -> Cons (f x) (\_ -> map f xs ()) Empty -> Empty Here, the call to map is more visibly in tail position. So I would say that in Haskell, tail-call optimization is just as important as, for example, in Scheme. But tail positions are not defined syntactically, but semantically, depending on the strictness properties of the program. Tillmann
 
            On Wednesday 16 March 2011 18:31:00, Yves Parès wrote:
Hello,
A question recently popped into my mind: does lazy evaluation reduce the need to "proper" tail-recursion? I mean, for instance :
fmap f [] = [] fmap f (x:xs) = f x : fmap f xs
Here fmap is not tail-recursive, but thanks to the fact that operator (:) is lazy, I think that it may still run in constant space/time, am I right?
Yes, and a tail-recursive map couldn't run in constant space, as far as I can see (time is O(length) for both of course, if the result is compeltely consumed). Tail recursion is good for strict stuff, otherwise the above pattern - I think it's called guarded recursion - is better, have the recursive call as a non-strict field of a constructor.
 
            Yes, and a tail-recursive map couldn't run in constant space
Yes, I meant "if you are consuming it just once immediately".
the above pattern [...] is better, have the recursive call as a non-strict field of a constructor.
Which pattern? Mine or Tillman's? Or both?
2011/3/16 Daniel Fischer 
On Wednesday 16 March 2011 18:31:00, Yves Parès wrote:
Hello,
A question recently popped into my mind: does lazy evaluation reduce the need to "proper" tail-recursion? I mean, for instance :
fmap f [] = [] fmap f (x:xs) = f x : fmap f xs
Here fmap is not tail-recursive, but thanks to the fact that operator (:) is lazy, I think that it may still run in constant space/time, am I right?
Yes, and a tail-recursive map couldn't run in constant space, as far as I can see (time is O(length) for both of course, if the result is compeltely consumed).
Tail recursion is good for strict stuff, otherwise the above pattern - I think it's called guarded recursion - is better, have the recursive call as a non-strict field of a constructor.
 
            On Wednesday 16 March 2011 20:02:54, Yves Parès wrote:
Yes, and a tail-recursive map couldn't run in constant space
Yes, I meant "if you are consuming it just once immediately".
And that's what, to my knowledge, is impossible with tail recursion. A tail recursive map/fmap would have to traverse the entire list before it could return anything.
the above pattern [...] is better, have the recursive call as a non-strict
field of a constructor.
Which pattern? Mine or Tillman's? Or both?
Yours/the Prelude's. I hadn't seen Tillmann's reply yet when I wrote mine. In map f (x:xs) = (:) (f x) (map f xs) the outermost call is a call to a constructor [that is not important, it could be a call to any sufficiently lazy function, so that you have a partial result without traversing the entire list] which is lazy in both fields, so a partial result is returned immediately. If the element (f x) or the tail is not needed, it won't be evaluated at all. If there are no other references, the (f x) can be garbage collected immediately after being consumed/ignored. Tillmann:
data EvaluatedList a
= Cons a (List a)
| Empty
type List a
= () -> EvaluatedList a
map :: (a -> b) -> (List a -> List b) map f xs
= \_ -> case xs () of
Cons x xs -> Cons (f x) (\_ -> map f xs ()) Empty -> Empty
Here, the call to map is more visibly in tail position.
According to the definition of tail recursion that I know, that's not tail recursive. By that, a function is tail-recursive if the recursive call (if there is one) is the last thing the function does, which in Haskell would translate to it being the outermost call. Thus a tail recursive map would be map some args (x:xs) = map other args' xs , with a worker: map f = go [] where go ys [] = reverse ys go ys (x:xs) = go (f x:ys) xs
 
            Hi, Daniel Fischer wrote:
data EvaluatedList a
= Cons a (List a)
| Empty
type List a
= () -> EvaluatedList a
map :: (a -> b) -> (List a -> List b) map f xs
= \_ -> case xs () of
Cons x xs -> Cons (f x) (\_ -> map f xs ()) Empty -> Empty
Here, the call to map is more visibly in tail position.
According to the definition of tail recursion that I know, that's not tail recursive.
My point is that the call to map is in tail position, because it is the last thing the function (\_ -> map f xs ()) does. So it is not a tail-recursive call, but it is a tail call. Of course, (\_ -> map f xs ()) does not occur literally in the Haskell implementation of map, but the runtime behavior of the Haskell implementation of map is similar to the runtime behavior of the code above in a strict language. Let's look at the following code: countdown n = if n == 0 then 0 else foo (n - 1) if' c t e = if c then t else e countdown' n = if' (n == 0) 0 (foo (n - 1)) countdown is clearly tail-recursive. Because of Haskell's non-strict semantics, countdown and countdown' have the same runtime behavior. I therefore submit that countdown' is tail-recursive, too. So I think that in a non-strict language like Haskell, we need to define "tail position" semantically, not syntactically. Tillmann
 
            On Wednesday 16 March 2011 21:44:36, Tillmann Rendel wrote:
My point is that the call to map is in tail position, because it is the last thing the function (\_ -> map f xs ()) does. So it is not a tail-recursive call, but it is a tail call.
Mmmm, okay, minor terminology mismatch, then. Makes sense, but is not what I'm used to. I'd say it is a tail-call of Cons's second argument, and the tail call of map would be Cons, so tail-call is not transitive.
Of course, (\_ -> map f xs ()) does not occur literally in the Haskell implementation of map, but the runtime behavior of the Haskell implementation of map is similar to the runtime behavior of the code above in a strict language.
Let's look at the following code:
countdown n = if n == 0 then 0 else foo (n - 1)
s/foo/countdown/ presumably
if' c t e = if c then t else e countdown' n = if' (n == 0) 0 (foo (n - 1))
s/foo/countdown'/
countdown is clearly tail-recursive. Because of Haskell's non-strict semantics, countdown and countdown' have the same runtime behavior. I therefore submit that countdown' is tail-recursive, too.
Formally, not according to the previously mentioned definition, but in terms of generated code/runtime behaviour, of course, so
So I think that in a non-strict language like Haskell, we need to define "tail position" semantically, not syntactically.
I think you're right.
Tillmann
Cheers, Daniel
 
            Hi, Daniel Fischer wrote:
Let's look at the following code:
countdown n = if n == 0 then 0 else foo (n - 1)
s/foo/countdown/
presumably
if' c t e = if c then t else e countdown' n = if' (n == 0) 0 (foo (n - 1))
s/foo/countdown'/
Yes to both substitutions. Looks like I need an email client with ghc integration. Tillmann
 
            And that's what, to my knowledge, is impossible with tail recursion. A tail recursive map/fmap would have to traverse the entire list before it could return anything.
Now that you say it, yes, you are right. Tail recursion imposes strictness,
since only the very last call can return something.
Can a type signature give you a hint about whether a function evaluates
some/all of its arguments (i.e. is strict/partially strict/lazy), or do you
have to look at the implementation to know?
2011/3/16 Daniel Fischer 
On Wednesday 16 March 2011 20:02:54, Yves Parès wrote:
Yes, and a tail-recursive map couldn't run in constant space
Yes, I meant "if you are consuming it just once immediately".
And that's what, to my knowledge, is impossible with tail recursion. A tail recursive map/fmap would have to traverse the entire list before it could return anything.
the above pattern [...] is better, have the recursive call as a non-strict
field of a constructor.
Which pattern? Mine or Tillman's? Or both?
Yours/the Prelude's. I hadn't seen Tillmann's reply yet when I wrote mine. In
map f (x:xs) = (:) (f x) (map f xs)
the outermost call is a call to a constructor [that is not important, it could be a call to any sufficiently lazy function, so that you have a partial result without traversing the entire list] which is lazy in both fields, so a partial result is returned immediately. If the element (f x) or the tail is not needed, it won't be evaluated at all. If there are no other references, the (f x) can be garbage collected immediately after being consumed/ignored.
Tillmann:
data EvaluatedList a
= Cons a (List a)
| Empty
type List a
= () -> EvaluatedList a
map :: (a -> b) -> (List a -> List b) map f xs
= \_ -> case xs () of
Cons x xs -> Cons (f x) (\_ -> map f xs ()) Empty -> Empty
Here, the call to map is more visibly in tail position.
According to the definition of tail recursion that I know, that's not tail recursive. By that, a function is tail-recursive if the recursive call (if there is one) is the last thing the function does, which in Haskell would translate to it being the outermost call.
Thus a tail recursive map would be
map some args (x:xs) = map other args' xs
, with a worker:
map f = go [] where go ys [] = reverse ys go ys (x:xs) = go (f x:ys) xs
 
            On Wednesday 16 March 2011 22:03:51, Yves Parès wrote:
Can a type signature give you a hint about whether a function evaluates some/all of its arguments (i.e. is strict/partially strict/lazy), or do you have to look at the implementation to know?
Cheating, with GHC, a magic hash tells you it's strict ( foo :: Int# -> Double# -> Double ). But generally, a type signature can give at most a hint, because the implementation could always be foo _ = undefined -- [], Nothing, 0, whatever the result type supports and hints for laziness tend to be stronger than hints for strictness ( const :: a -> b -> a hints strongly that it's lazy in the second argument, but it could still be strict; arguments of type Int, Double or the like have a better than average chance of being strict). The only way to know is looking at the implementation, but if the docs say something about strictness, that should be good enough unless you have reason to suspect they're wrong.
 
            On Wed, 16 Mar 2011, Daniel Fischer wrote:
Tail recursion is good for strict stuff, otherwise the above pattern - I think it's called guarded recursion - is better, have the recursive call as a non-strict field of a constructor.
In http://haskell.org/haskellwiki/Tail_recursion it is also called 'guarded recursion', however the linked article is yet to be written ...
participants (4)
- 
                 Daniel Fischer Daniel Fischer
- 
                 Henning Thielemann Henning Thielemann
- 
                 Tillmann Rendel Tillmann Rendel
- 
                 Yves Parès Yves Parès