[Haskell-cafe] Lazy evaluation and tail-recursion

Yves Parès limestrael at gmail.com
Wed Mar 16 22:03:51 CET 2011


 > 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 <daniel.is.fischer at googlemail.com>

> 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
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110316/33ada6ed/attachment.htm>


More information about the Haskell-Cafe mailing list