[Haskell-beginners] Thompson Exercise 9.13

Daniel Fischer daniel.is.fischer at web.de
Thu Jul 15 15:27:27 EDT 2010


On Thursday 15 July 2010 16:06:01, Patrick LeBoutillier wrote:
> Hi,
>
> >> *last* :: [a] -> a
> >> last xs = head $ foldr f [] xs
> >>  where f :: a -> [a] -> [a]
> >>        f x [] = [x]
> >>        f x ys = ys ++ [x]
> >
> > a) in the second branch of f, you don't actually need to concatenate,
> >
> > f x [] = [x]
> > f _ ys = ys
> >
> > works too, but is faster.
>
> Why is it faster? I thought that the laziness would cause the
> concatenation not to be evaluated at all since we are taking the head
> of the list.
> Is that not the case?

That is (almost) the case (otherwise the performance of the first version 
would be worse), but for each list element, the pattern match in the folded 
function forces one evaluation step of a (++)-application [and for that, 
one further pattern match], thus it has to do more work.

Remember,

[] ++ ys = ys
(x:xs) ++ ys = x : (xs ++ ys)

If we look at what happens with

f1 x [] = [x]
f1 x ys = ys ++ [x]

in a generic step:

f1 x (f1 y zs)
~> case f1 y zs of { [] -> [x]; w:ws -> (w:ws) ++ [x] }
~> case (case zs of { [] -> [y]; v:vs -> (v:vs) ++ [y] }) of
        { [] -> [x]; w:ws -> (w:ws) ++ [x] }
-- let's assume zs is not null
~> case (v:vs) ++ [y] of { [] -> [x]; w:ws -> (w:ws) ++ [x] }
~> case (case (v:vs) of { [] -> [y]; u:us -> u:(us ++ [y]) }) of
        { [] -> [x]; w:ws -> (w:ws) ++ [x] }
~> case v:(vs ++ [y]) of
        { [] -> [x]; w:ws -> (w:ws) ++ [x] }
~> (v:(vs ++ [y])) ++ [x]

and with

f2 x [] = [x]
f2 _ ys = ys

f2 x (f2 y zs)
~> case f2 y zs of { [] -> [x]; w:ws -> (w:ws) }
~> case (case zs of { [] -> [y]; v:vs -> (v:vs) }) of
        { [] -> [x]; w:ws -> (w:ws) }
-- again, assume zs is not null
~> case v:vs of
        { [] -> [x]; w:ws -> (w:ws) }
~> v:vs

In the former, at each step, to determine the branch of f1, an expression 
of the form (us ++ vs) has to be matched against [].
For that, us has to be matched against [].
Typically, us is of the form (u:us'), so (us ++ vs) is rewritten to
u:(us' ++ vs).
That doesn't match [], so the second branch of f1 is taken and we get
(u:(us' ++ vs)) ++ [x], again wrapping the first (:) in a (++)-application.
For each list-element, we must evaluate a (++)-application one step.

In the latter, once at the end of the list a (y:[]) is produced, all that 
happens is pattern matching and passing the value unmodified to the next 
pattern match.

>
> Thanks,
>
> Patrick


Cheers,
Daniel



More information about the Beginners mailing list