Re: [Haskell-cafe] Re: Difference lists and ShowS

2008-01-10 Thread Henning Thielemann

On Wed, 9 Jan 2008, apfelmus wrote:

 So, difference lists are no eierlegende wollmilchsau either.

LEO's forum suggests 'swiss army knife' as translation. :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Difference lists and ShowS

2008-01-10 Thread Achim Schneider
Henning Thielemann [EMAIL PROTECTED] wrote:

 
 On Wed, 9 Jan 2008, apfelmus wrote:
 
  So, difference lists are no eierlegende wollmilchsau either.
 
 LEO's forum suggests 'swiss army knife' as translation. :-)

But you really need one with 5 differently-sized blades plus three
spezialized carving blades, an USB stick, microscope, 13 kinds of torx,
imbus etc drivers each, a tv set (analogue/digital) with unfoldable
touchscreen, at least 3-band GSM and WiFi connectivity, hydraulic car
jack and chain saw to award it with the term egg-laying woolmilkpig.


-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Difference lists and ShowS

2008-01-10 Thread apfelmus

Achim Schneider wrote:

Henning Thielemann wrote:


apfelmus wrote:


So, difference lists are no eierlegende wollmilchsau either.



LEO's forum suggests 'swiss army knife' as translation. :-)


But you really need one with 5 differently-sized blades plus three
spezialized carving blades, an USB stick, microscope, 13 kinds of torx,
imbus etc drivers each, a tv set (analogue/digital) with unfoldable
touchscreen, at least 3-band GSM and WiFi connectivity, hydraulic car
jack and chain saw to award it with the term egg-laying woolmilkpig.


But even such knives still can't lay eggs :(


Regards,
apfelmus

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Difference lists and ShowS

2008-01-10 Thread ajb

G'day all.

Quoting Achim Schneider [EMAIL PROTECTED]:


But you really need one with 5 differently-sized blades plus three
spezialized carving blades, an USB stick, microscope, 13 kinds of torx,
imbus etc drivers each, a tv set (analogue/digital) with unfoldable
touchscreen, at least 3-band GSM and WiFi connectivity, hydraulic car
jack and chain saw to award it with the term egg-laying woolmilkpig.


So a better translation into British engineering language might be
Heath Robinson?

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Difference lists and ShowS

2008-01-10 Thread Achim Schneider
[EMAIL PROTECTED] wrote:

 G'day all.
 
 Quoting Achim Schneider [EMAIL PROTECTED]:
 
  But you really need one with 5 differently-sized blades plus three
  spezialized carving blades, an USB stick, microscope, 13 kinds of
  torx, imbus etc drivers each, a tv set (analogue/digital) with
  unfoldable touchscreen, at least 3-band GSM and WiFi connectivity,
  hydraulic car jack and chain saw to award it with the term
  egg-laying woolmilkpig.
 
 So a better translation into British engineering language might be
 Heath Robinson?
 
Not really. To give you the perfect cs example, take a look at emacs:
eight megabytes and continuous swapping, a whole OS with any app and
library you could ever dream of, but not one decent editor.

See, on the one hand that beast is every farmer's dream, but then you
can't butcher the pig 'cos you want to have its milk, wool and eggs..

http://catb.org/jargon/html/C/creeping-featuritis.html
is the associated plague.

Outlook reminds me of it, too: I spend half a paid hour configuring it,
changing everything, from default message format to quote behaviour and
similar.


-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Difference lists and ShowS

2008-01-09 Thread apfelmus

Albert Y. C. Lai wrote:

apfelmus wrote:
I don't know a formalism for easy reasoning about time in a lazy 
language. Anyone any pointers? Note that the problem is already 
present for difference lists in strict languages.


http://homepages.inf.ed.ac.uk/wadler/topics/strictness-analysis.html

especially strictness analysis aids time analysis.


Ah, of course, thanks. Together with

  D. Sands. Complexity Analysis for a Lazy Higher-Order Language.
  http://citeseer.ist.psu.edu/291589.html

for the higher-order case, a satisfactory analysis can be put together.


The formalism is basically as follows: for a function f, let f^T denote 
the time needed to execute it to weak normal form given that it's 
arguments are already in weak normal form. Weak normal form = full 
normal form for algebraic values and lambda-abstraction for functions = 
what you'd expect in a strict language. Plain values = nullary 
functions. For instance


  (++)^T [] ys = 1 + ys^T = 1
  (++)^T (x:xs) ys = 1 + (x:(xs ++ ys))^T
   = 1 + (++)^T xs ys + xs^T + ys^T  -- (:) is free
   = 1 + (++)^T xs ys
 ==
  (++)^T xs ys = O(length xs)

Substituting a function application by the function body is counted as 1 
time step, that's where the  1 +  comes from.



For difference lists, we have

  (.)^T f g = O(1)

since it immediately returns the lambda-abstraction  \x - f(g x) . Now, 
we missed something important about difference lists namely the function


  toList f = f []

that turns a difference list into an ordinary list and this function is 
O(n). In contrast, The pendant for ordinary lists, i.e. the identity 
function, is only O(1). Why is it O(n)? Well, (.) itself may be O(1) but 
it constructs a function that needs lots of time to run. In particular


  (f . g)^T [] = ((\x-f (g x))[])^T
   = 1 + (f (g []))^T
   = 1 + f^T (g []) + (g [])^T
   = 1 + f^T (g []) + g^T []

So, to analyze higher-order functions, we simply have to keep track of 
the size of the returned functions (more precisely, Sands uses 
cost-closures). The above reduces to


  (f . g)^T [] = 1 + f^T [] + g^T []

Since our difference lists don't care of what they are prepended to

  f^T xs = f^T []

Cheating a bit with the notation, we can write

  toList^T (f . g) = 1 + toList^T f + toList^T g

This means that a difference list build out of  n  elements by  m 
applications of (.) will take  O(n + m) time. This is the same as O(m) 
because m = n , our lists are concatenations of singletons. That's not 
O(n) as anticipated, but it's alright: a concatenation of  m  empty 
lists is empty but clearly takes O(m) time, so the number of 
concatenations matters.



Since difference lists offer such a good concatenation, why not replace 
ordinary lists entirely? Well, the problem is that we have another 
function that should run fast, namely  head . For ordinary lists,


  head^T xs = O(1)

but for difference lists, we have

  (head . toList)^T f = O(m) which is = O(n)

in the worst case, lazy evaluation notwithstanding. How to analyze lazy 
evaluation? Wadler's approach is to add an extra argument to every 
expression which says how much of the expression is to be evaluated. 
This extra information can be encoded via projections. But I think it's 
sufficient here to let (head expr)^T symbolize the time to reduce  expr 
 to weak head normal form. For example,


  (head . toList)^T (f . g) = 1 + (head . toList)^T f

assuming that  f  is nonempty. But due to the  1 + , any left-nested 
composition like


  head . toList $ (((a . b) . c) . d) . e

still needs O(m) time. So, difference lists are no eierlegende 
wollmilchsau either.




Regards,
apfelmus

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Difference lists and ShowS

2008-01-03 Thread Henning Thielemann

On Thu, 3 Jan 2008, Achim Schneider wrote:

 Henning Thielemann [EMAIL PROTECTED] wrote:

  Sometimes I believed that I understand this reason, but then again I
  do not understand. I see that left-associative (++) like in
((a0 ++ a1) ++ a2) ++ a3
   would cause quadratic time. But (++) is right-associative and
  'concat' is 'foldr'. They should not scan the leading lists more than
  once. Also
http://en.wikipedia.org/wiki/Difference_list
   doesn't answer this question. Where exactly is the problem?
 

 | The shows functions return a function that prepends the output String
 | to an existing String. This allows constant-time concatenation of
 | results using function composition.

How is constant-time concatenation meant? If I process all list
elements, it will need linear time. If I do not touch any element, I will
need no time due to lazy evaluation. As far as I know, lazy evaluation is
implemented by returning a union of a routine generating the actual value
and the value, if it was already computed. Thus, calling (++) returns a
function internally.

 I figure it's (constant vs. linear) vs. (linear vs. quadratic), for
 more involved examples.

I can't see it. If I consider (x++y) but I do not evaluate any element of
(x++y) or only the first element, then this will need constant time. If I
evaluate the first n elements I need n computation time units. How is (.)
on difference lists faster than (++) here?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Difference lists and ShowS

2008-01-03 Thread Achim Schneider
Henning Thielemann [EMAIL PROTECTED] wrote:

  I figure it's (constant vs. linear) vs. (linear vs. quadratic), for
  more involved examples.
 
 I can't see it. If I consider (x++y) but I do not evaluate any
 element of (x++y) or only the first element, then this will need
 constant time. If I evaluate the first n elements I need n
 computation time units. How is (.) on difference lists faster than
 (++) here?

It's in multiple calls to length if you do ((x++y)++z), the first run
over x can be avoided. It basically gets rewritten to (x++y++z) by
another level of abstraction.


-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Difference lists and ShowS

2008-01-03 Thread apfelmus

Henning Thielemann wrote:

I can't see it. If I consider (x++y) but I do not evaluate any element of
(x++y) or only the first element, then this will need constant time. If I
evaluate the first n elements I need n computation time units. How is (.)
on difference lists faster than (++) here?


That's a very good question. Basically, the problem is: how to specify 
the time complexity of an operation under lazy evaluation?



You argue that (++) is constant time in the sense that evaluating (x ++ 
y) to WHNF is O(1) when x and y are already in WHNF. Same for (.). This 
is indeed correct but apparently fails to explain why (.) is any better 
than (++). Help!



Of course, this very paradox shows that just looking at WHNF is not 
enough. The next best description is to pretend that our language is 
strict and to consider full normal form


  x in NF, y in NF -- (x++y) evaluates to NF in O(length x) time

Even when x and y are not in normal form, we know that evaluating the 
expression (x ++ y) takes


  O(x ++ y) ~ O(length x) + O(x) + O(y)

time to evaluate to NF. Here, O(e) is the time needed to bring the 
expression e into NF first. This approach now explains that (++) takes 
quadratic time when used left-associatively


  O((x ++ y) ++ z) ~   O(length x + length y) + O(length x)
 + O(x) + O(y) + O(z)

instead of the expected

  O((x ++ y) ++ z) ~ O(x) + O(y) + O(z)

or something (only up to constant factors and stuff, but you get the 
idea). Note that considering NFs is still only an approximation since


  O(head (qsort xs)) ~ O(n) + O(xs)  where n = length xs

instead of the expected

  O(head (qsort xs)) ~ O(qsort xs)
 ~ O(n log n) + O(xs) where n = length xs

thanks to lazy evaluation. Also note that despite considering full 
normal forms, we can express some laziness with this by giving timings 
for an expression in different contexts like


  O(take n ys)
  O(head ys)

instead of only O(ys). Same for parameters with something like

  O(const x) ~ O(1)

instead of the anticipated O(const x) ~ O(x). (For lazy data structures, 
there are better ways to take laziness into account.)




With difference lists I write

shows L . (shows T . shows R)
(shows LL . (showsLT . shows LR)) . (shows T . shows R)
((shows LLL . (shows LLT . shows LLR)) . (showsLT . shows LR)) . (shows T . 
shows R)

I still need to resolve three (.) until I get to the first character of
the result string, but for the subsequent characters I do not need to
resolve those dots. In the end, resolution of all (.) may need some time
but then concatenation is performed entirely right-associative. Seems to
be that this is the trick ...


So far so good, but the problem now is that analyzing (.) with full 
normal forms is doomed since this would mean to evaluate things under 
the lambda which may take less time than doing call-by-need reductions. 
Still, we somehow have


  O(x . y) ~ O(x) + O(y)

which is better than O(x ++ y) but I'm not quite sure how to make this 
exact yet.



In the end, the above O(e)s are just random doodles conjured out of the 
hat, I don't know a formalism for easy reasoning about time in a lazy 
language. Anyone any pointers? Note that the problem is already present 
for difference lists in strict languages.




Regards,
apfelmus

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Difference lists and ShowS

2008-01-03 Thread Achim Schneider
apfelmus [EMAIL PROTECTED] wrote:

O((x ++ y) ++ z) ~   O(length x + length y) + O(length x)
   + O(x) + O(y) + O(z)

I would say that it's ~ O(length x) + O(length $ x ++ y) + O(2 * list
mangling)

-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Difference lists and ShowS

2008-01-03 Thread Albert Y. C. Lai

apfelmus wrote:
I don't know a formalism for easy reasoning about time in a lazy 
language. Anyone any pointers? Note that the problem is already present 
for difference lists in strict languages.


http://homepages.inf.ed.ac.uk/wadler/topics/strictness-analysis.html

especially strictness analysis aids time analysis.

Much CPO math is involved, but I view it as: a function gives you 
output; if you know how much of the output you use, you can deduce how 
much work the function goes through.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe