if (++) were left associative ?

Konst Sushenko konsu@microsoft.com
Sun, 7 Apr 2002 12:16:49 -0700


This one helped. Thanks.

'reduction' was the key word that made it clear for me. It is not that =
left associated (++) reconstructs the list once and again (although one =
can say that) it is just that to return the head from the recursive =
invocations takes quadratic number of reductions. Right?

konst

> -----Original Message-----
> From: Jay Cox [mailto:sqrtofone@yahoo.com]=20
> Sent: Sunday, April 07, 2002 11:09 AM
> To: Konst Sushenko
> Cc: haskell-cafe@haskell.org; Jon Fairbairn
> Subject: Re: if (++) were left associative ?=20
>=20
>=20
> On Sun, 7 Apr 2002, Jon Fairbairn wrote:
>=20
> > The answer is that you have to evaluate ((([] ++ [1]) ++
> > [2]) ++ [3]) before you can find it, and to get that, you
> > have to evaluate (([] ++ [1]) ++ [2]) and so on.
> >
> >
> > In the other case, you can get the head of (a:...)++ (b ++
> > c) by evaluating only the first steps of the first (++).
> >
> >
> > Does that help?
> >
> >   J=F3n
> >
>=20
>=20
> Just to add a bit.  "evaluate" is such a fuzzy word,=20
> especially in a lazy
> language.  You must know the context of the expression in=20
> order to know
> how much of it is actually evaluated*.
>=20
> (* Eventually, the context of all expressions in haskell will be the
> evaluation of something in the IO monad, but generally you don't
> have to go that far in your reasoning about contexts and stuff.)
>=20
>=20
> Ok.  I shall now attempt to explain a bit more deeply the differences
> between the evaluation expressions which use a left associative append
> versis expressions uing a right associative append.
>=20
>=20
>=20
>=20
>=20
> In the following,"tail" means any arbitrary tail of a list.=20
> Also, for the
> sake of argument, assume : binds closer than ++ and function=20
> application
> so we dont have to mess with so many damn parentheses. (in=20
> reality I don't
> think anything binds closer than function application in Haskell.)
>=20
> the definition of ++ is like
>=20
> []     ++ b =3D b
> (l:ls) ++ b =3D l:(ls++b)
>=20
>=20
> applist =3D ((w:tail ++ x:tail) ++ y:tail) ++ z:tail
>=20
> This can be rewritten as the following, so we can litterally see
> the leftmost-outermost-reduction.
>=20
> applist =3D (++) ((++) ((++) w:tail x:tail) y:tail) z:tail
>=20
> ick! lets say f=3D(++) (or that f is the same function as the append
> operator (++))
>=20
> applist =3D f (f (f w:tail x:tail) y:tail) z:tail
>=20
>=20
>=20
> Alright. Now say we want the head of this applist. So lets use
> the head function.
>=20
> head patern matches against that thing, causing
> a reduction of the outmost f.  Since f
> pattern matches against its first arguement,
> it must cause a reduction in the second f
> in that expression, and likewise the third f.
> The third f will succeed in its pattern match,
> namely (w:tail).
>=20
> Now, f, which was (++), will get unfolded.
> using the original definition of (++)
> (l:ls) ++ b =3D l:(ls++b)
>=20
> this becomes
> (w:tail) ++ (x:tail) =3D w:(tail ++ x:tail)
>=20
> (which in our notation is w:(f tail x:tail))
>=20
> substuting our unfolding back into applist and continuing with
> reductions:
>=20
>    f  (f (f w:tail x:tail)  y:tail)  z:tail
> -> f  (f w:(f tail x:tail)  y:tail) z:tail
> -> f  w:(f (f tail x:tail)  y:tail)  z:tail
> -> w:(f(f(f tail x:tail) y:tail) z:tail)
>=20
> so its not like it will take length (w:tail) + length (x:tail) +
> length(y:tail) reductions or whatever, but it does take
> 3 reductions to get to the head, AND WILL BY NECESSITY take 3
> reductions to get each element of the rest of the tail of w:tail.
>=20
> I >think< in the end, if you need all of applist, you will need
> something like
>=20
> 3*length (w:tail) + 2*length(x:tail) + length(y:tail)
>=20
> reductions of f.
>=20
> That is definitely NOT linear with
> (length x:tail) + (length y:tail) + (length z:tail)
>=20
>=20
>=20
>=20
> Now. Lets try go get the head of
>=20
> w:tail ++ (x:tail ++ (y:tail ++ z:tail))
>=20
> doing like before with (++), that is
>=20
> f w:tail (f x:tail (f y:tail z:tail))
>=20
> and now f pattern matches, etc.
>=20
>=20
> ->w:(f tail (f x:tail (f y:tail z:tail)))
>=20
>=20
> and thats the ONLY reduction necessary.
>=20
> getting all of applist should only require something close to
>=20
> (length x:tail) + (length y:tail) + (length z:tail)
>=20
> reductions of f.
>=20
>=20
>=20
> I'm sure I'm not %100 accurate here, (and It's not worth the effort
> for this message!) but I hope this gives more insight and not
> more confusion!
>=20
> Cheers,
>=20
>=20
> Jay Cox
>=20
>=20
>=20