Is lazyness make big difference?

Hi all, (Another topic stolen from a Russian forum discussion). As everyone know, there are lot of strict languages, that have possibilities to "switch on" lazy evaluation when needed. But the examples that I saw on Haskell, there was not much use of lazy evaluation, often there were just several lazy points, and the rest could be done strictly without loss of generality. For example, in finding primes: main = print primes primes = 2:filter is_prime [3,5..] is_prime n = all (\p-> n `mod` p /= 0) (takeWhile (\p-> p*p<=n) primes) We can rewrite this in strict languages with lazy constructs. For example, in Scala (of course stream is not only lazily evaluated thing there) def main(args: Array[String]): Unit = { val n = Integer.parseInt(args(0)) System.out.println(primes(ints(2)) take n toList) } def primes(nums: Stream[Int]): Stream[Int] = Stream.cons(nums.head, primes ((nums tail) filter (x => x % nums.head != 0)) ) def ints(n: Int): Stream[Int] = Stream.cons(n, ints(n+1)) I think the Haskell solution is more compact due to syntactic sugar, curring and "parentheses-free-ness", *not* lazy evaluation. According to one guy's analogy: the Real World is strict - in order to drink tea, you have to put the cattle on the fire, wait until water boils, brew tea and then drink. Not the cattle is put on the fire, water boils and the tea is brewed when you take the empty cup to start drinking. :-) The question is the following: how big the gap between strict languages with lazy constructs and Haskell? Does the default lazyness have irrefutable advantage over default strictness? Thank you for the attention. With best regards, Nick.

nick.linker:
Hi all, (Another topic stolen from a Russian forum discussion). As everyone know, there are lot of strict languages, that have possibilities to "switch on" lazy evaluation when needed. But the examples that I saw on Haskell, there was not much use of lazy evaluation, often there were just several lazy points, and the rest could be done strictly without loss of generality. For example, in finding primes:
Some good examples are on the shootout: The lazily generated trees in particular, http://shootout.alioth.debian.org/gp4/benchmark.php?test=binarytrees&lang=all (note the much smaller memory footprint) And here, a lazy infinite DNA sequence generator: http://shootout.alioth.debian.org/gp4/benchmark.php?test=fasta&lang=ghc&id=2 (the cycle alu part generates an infinite dna stream, which we then print only as much of as we need. Greatly simplifies the code). -- Don

Nick wrote:
Hi all,
(Another topic stolen from a Russian forum discussion).
As everyone know, there are lot of strict languages, that have possibilities to "switch on" lazy evaluation when needed.
But the examples that I saw on Haskell, there was not much use of lazy evaluation, often there were just several lazy points, and the rest could be done strictly without loss of generality. For example, in finding primes: I think the Haskell solution is more compact due to syntactic sugar, curring and "parentheses-free-ness", *not* lazy evaluation.
Hi, I think a big advantage is that programs can be written without regard for whether or not a value will in the long run actually be evaluated. For me one of the best examples of this is that of logging within a compiler. Consider a compiler which operates roughly as such compileProgram :: String -> IO () compileProgram program = let (log, abstract) = parse program (log2, typedProgram) = typeCheck abstract log2 (log3, convertedProgram) = convertToIntermediate typedProgram log2 (log4, convertedToAssembly) = convertToAssembly convertedProgram log3 in do writeFile "a.asm" (show convertedToAssembly) writeFile "a.log" (show log4) Now each of the intermediate transforming calls will produce some logging information which is added to the current log. Some of these will require quite heavy traversing of the entire program, which will almost certainly require auxiliary functions. Suppose we want to allow the suppressing of the log information ie: compileProgram :: String -> Bool -> IO () compileProgram program logOrNot = let (log, abstract) = parse program (log2, typedProgram) = typeCheck abstract log2 (log3, convertedProgram) = convertToIntermediate typedProgram log2 (log4, convertedToAssembly) = convertToAssembly convertedProgram log3 in do writeFile "a.asm" (show convertedToAssembly) if logOrNot then writeFile "a.log" (show log4) else return () Now if this is a strict language we have to go and modify all the intermediate functions to first of all take in a boolean and then use that to decide whether or not to produce any logging information. With a lazy language though, we don't need to do that, we're already done, no logging information will be produced if 'logOrNot' is false, because it will never be forced to evaluate the thunk.
According to one guy's analogy: the Real World is strict - in order to drink tea, you have to put the cattle on the fire, wait until water boils, brew tea and then drink. Not the cattle is put on the fire, water boils and the tea is brewed when you take the empty cup to start drinking. :-)
Yes true, but you don't just boil up the kettle and brew the tea unless you have first asked if anyone actually wants tea.
The question is the following: how big the gap between strict languages with lazy constructs and Haskell? Does the default lazyness have irrefutable advantage over default strictness?
Thank you for the attention.
With best regards, Nick.

Hi, I think a big advantage is that programs can be written without regard for whether or not a value will in the long run actually be evaluated. For me one of the best examples of this is that of logging within a compiler.
[example goes here]
Now if this is a strict language we have to go and modify all the intermediate functions to first of all take in a boolean and then use that to decide whether or not to produce any logging information. With a lazy language though, we don't need to do that, we're already done, no logging information will be produced if 'logOrNot' is false, because it will never be forced to evaluate the thunk. Yes, I agree, lazy evaluation is important, but unfortunately you didn't convince me that it should be on *by default*. In strict languages we usually some facility like macros, and with them we can do everything
Alan, like that (and with better performance). Or, we could make the logging function (called by functions inside convertToIntermediate, convertToAssembly etc) as lazy (mark them as lazy or change them to lazy form). For example, Scala again: /* Lazily compute the logger. The computation will not start running until the value of 'logger' is actually requested. */ var logger = lazy({ Logging.getLogger() }) /* This will start the computation */ logger.debug("medved") /* No delay to compute the logger again, as it has already been calculated */ logger.debug("preved")
According to one guy's analogy: the Real World is strict - in order to drink tea, you have to put the kettle on the fire, wait until water boils, brew tea and then drink. Not the kettle is put on the fire, water boils and the tea is brewed when you take the empty cup to start drinking. :-) Yes true, but you don't just boil up the kettle and brew the tea unless you have first asked if anyone actually wants tea. Hmm, the analogy is very flexible, and yours argument is also reasonable. (Oops, yes - kettle should be put on the fire, not cattle :-D)
Best regards, Nick

Nick wrote:
/* Lazily compute the logger. The computation will not start running until the value of 'logger' is actually requested. */ var logger = lazy({ Logging.getLogger() })
/* This will start the computation */ logger.debug("medved")
/* No delay to compute the logger again, as it has already been calculated */ logger.debug("preved")
It seems you miss the point here: not only logger should be lazy, but all calls to logger's methods: logger.debug(formatLongMessage(args)); // formatLongMessage should not // waste CPU cycles if debug // logging is off

Allan Clark wrote:
For me one of the best examples of this is that of logging within a compiler. Consider a compiler which operates roughly as such
compileProgram :: String -> IO () compileProgram program = let (log, abstract) = parse program (log2, typedProgram) = typeCheck abstract log (log3, convertedProgram) = convertToIntermediate typedProgram log2 (log4, convertedToAssembly) = convertToAssembly convertedProgram log3 in do writeFile "a.asm" (show convertedToAssembly) writeFile "a.log" (show log4)
Now each of the intermediate transforming calls will produce some logging information which is added to the current log.
It's a bit OT (off thread) but I think that it's better to appeal to the monoid structure of logs let (log, abstract ) = parse program (log2, typedProgram) = typeCheck abstract (log3, convertedProgram) = convertToIntermediate typedProgram (log4, convertedToAssembly) = convertToAssembly convertedProgram in show (mconcat [log,log2,log3,log4]) i.e. to use Monad.Writer in stead of Monad.State. The point is that for example 'typedProgram' does not really depend on the contents of 'log', but the dependencies in your code don't express this. One should switch from Log -> (a, Log) to (a, Log -> Log) or even (a, Log) if Log already has a natural monoid structure. Regards, apfelmus

i.e. to use Monad.Writer in stead of Monad.State. The point is that for example 'typedProgram' does not really depend on the contents of 'log', but the dependencies in your code don't express this. One should switch from
Log -> (a, Log)
to
(a, Log -> Log)
or even
(a, Log)
if Log already has a natural monoid structure. Yes of course you're quite right, in general I would have the last version ie (a, Log). I did not wish to muddy the example, but probably it was not helpful to have 'typedProgram' depend on the contents of 'log'.
regards allan

Quoth Nick, nevermore,
According to one guy's analogy: the Real World is strict - in order to drink tea, you have to put the cattle on the fire, wait until water boils, brew tea and then drink. Not the cattle is put on the fire, water boils and the tea is brewed when you take the empty cup to start drinking. :-)
I think the word you meant there is "kettle", since "cattle" are what get turned into burgers ;-) Still, the idea of water-boil-tea-brew happening by demand would probably save electricity in our energy-conscious world. Don't boil a full kettle for a single cuppa!
The question is the following: how big the gap between strict languages with lazy constructs and Haskell? Does the default lazyness have irrefutable advantage over default strictness?
That kinda leads into thoughts of the Turing tar-pit, where everything is possible but hopelessly obfuscated by the constraints of the language. I think default laziness, to answer your actual question, has advantage in terms of thought process. It helps me consider things in terms of dependencies. To go back to the analogy: in the strict style it's very easy to boil the kettle and then let the water go cold. This is a waste of energy (CPU time, or whatever). So whether it's *computationally* more valuable, I don't know. But I find that it helps me to order my thoughts about what a problem *needs*. Cheers, D. -- Dougal Stanton

2007/2/15, Dougal Stanton
Quoth Nick, nevermore,
According to one guy's analogy: the Real World is strict - in order to drink tea, you have to put the cattle on the fire, wait until water boils, brew tea and then drink. Not the cattle is put on the fire, water boils and the tea is brewed when you take the empty cup to start drinking. :-)
I think the word you meant there is "kettle", since "cattle" are what get turned into burgers ;-) Still, the idea of water-boil-tea-brew happening by demand would probably save electricity in our energy-conscious world. Don't boil a full kettle for a single cuppa!
An example of real world laziness, and where it pays off, is maybe the kanban system as used in manufactering: http://en.wikipedia.org/wiki/Kanban Not sure though if such so called real world examples actually add much to the discussion. Ultimately I think you need both lazy and strict evaluation; a reasonable default depends on the flavour of the particular language. Given Haskell, it seems lazy by default is the obvious choice (however I may feel that way simply because it _is_ that way :) )Strict just can't be the _only_ option, as it too often is. Kurt

Citing the quoted citation, or the cited quotation, or whatever:
According to one guy's analogy: the Real World is strict - in order to drink tea, you have to put the kettle on the fire, wait until water boils, brew tea and then drink. Not the kettle is put on the fire, water boils and the tea is brewed when you take the empty cup to start drinking.
etc. etc.... I have been advocating for years that independently of theoretical advantages, and some nice realizations (Bird et al), there is something more. The laziness is a terric ALGORITHMIC TOOL, making it possible to write equations, with intricate cross-reference between variables, and to transform them without moving a finger into implementable algorithms. There are no miracles, and if a variable references another one, which will be instantiated later, it cannot use directly the concerned values. But plenty of algorithms *may* be effective, since they defer the access to those "future" objects. I wrote a bunch of papers on this... Getting back to the Real World. The main issue - in my opinion - is that we do not code the Real World, whatever may be your personal philosophy. The models we code bear some peculiar relations to the models we *see* in our Plato cavern. Take for a pedagogic example, the issue of robotics, or, if you prefer, the animation of humans/animals, etc. The physical causality works as follows. The brain issues the orders which propagate sequentially through the nerves, make the articulations and the limbs move, and *finally* the end effector - the hand - grasps the kettle and put in on the fire. Anybody protests? Now, a robot, or an animated personage has a *scenario* to obey, to grasp the damn kettle, and to put it on the fire. The intermediate limbs and articulations must move accordingly. Now you will code all this... And you fall well inside the domain called the Inverse Kinematics issue, which may demand some horrible calculi, such as the evaluation of the pseudo-inverses of Jacobi matrices, but doesn't matter. You must *reason* differently. The hand "pulls" the elbow, which pulls the arm, which "says": "may dear brain, I need the following commands from you, in order that our terminal effector obey its scenario..." == Folks, this is no science fiction, but *ALL COMPLICATED ANIMATIONS* are done in this way. The IK is an established industrial domain, and in my humble opinion, the laziness IS the tool to code it in a readable manner (I work on this right now, but slowly...) Jerzy Karczmarczuk PS. BTW. The True Real World is quantum, not classical. A bottle of the most expensive champagne I can afford, to a guy who will convince me that the quantum world is strict in the computational sense of this word. In my opinion this category is not applicable at all...

Kudos to you for invoking Plato. This forum could use a bit of epistemological levity. Your passionate and quirky style reminds me of the "Laws of Form" by G. Spencer-Brown (http://en.wikipedia.org/wiki/Laws_of_form). One quibble: I work for a one of the world's largest 3-D visual effects studios (based in LA) and I can say with some authority that of the work I've seen, the vast amount of animation (complicated or not) both embedded in photo-realistic live action and in full-feature animation is NOT inverse kinematics, but forward kinematics in an endless chain of deformer layers, painstakingly and lovingly coerced through endless iterations into place. The "obvious benefits" of physical simulation, IK, and rule-based autonomous behavior inevitably run into the brick wall of a director whose inner vision cannot be easily converged on through any complicated function of few input parameters. Even motion capture (actual human motion) often needs tweaking to more effectively tell a story. Experienced animators can fake the IK part of this fairly quickly, in any case. As such, it is not lazy programming, but greedy programming that is prominent in my industry. Lazy algorithms work best when the goal is well understood and the algorithm takes shape during development. In visual effects, efficiency of process and predictability of result are paramount (pardon the pun), and algorithms that optimize these are well understood. It is the end effect that evolves by massaging and mutating these algorithms strategically. Often, the exact goal is not known even to the director until it appears out of a lineup (or "wedge", evaluated greedily) of countless variations. Perhaps your different experience is in the domain of robotics or games programming, which have entirely different goals and requirements. Dan Weston Senior Software Engineer Sony Pictures Imageworks NOTE: The opinions and observations expressed here are personal views expressed by me alone and do not necessarily reflect those of Sony Pictures, its subsidiaries, business partners, affiliates, or other employees thereof. jerzy.karczmarczuk@info.unicaen.fr wrote:
Citing the quoted citation, or the cited quotation, or whatever:
According to one guy's analogy: the Real World is strict - in order to drink tea, you have to put the kettle on the fire, wait until water boils, brew tea and then drink. Not the kettle is put on the fire, water boils and the tea is brewed when you take the empty cup to > start drinking.
etc. etc.... I have been advocating for years that independently of theoretical advantages, and some nice realizations (Bird et al), there is something more. The laziness is a terric ALGORITHMIC TOOL, making it possible to write equations, with intricate cross-reference between variables, and to transform them without moving a finger into implementable algorithms. There are no miracles, and if a variable references another one, which will be instantiated later, it cannot use directly the concerned values. But plenty of algorithms *may* be effective, since they defer the access to those "future" objects. I wrote a bunch of papers on this... Getting back to the Real World. The main issue - in my opinion - is that we do not code the Real World, whatever may be your personal philosophy. The models we code bear some peculiar relations to the models we *see* in our Plato cavern. Take for a pedagogic example, the issue of robotics, or, if you prefer, the animation of humans/animals, etc. The physical causality works as follows. The brain issues the orders which propagate sequentially through the nerves, make the articulations and the limbs move, and *finally* the end effector - the hand - grasps the kettle and put in on the fire. Anybody protests? Now, a robot, or an animated personage has a *scenario* to obey, to grasp the damn kettle, and to put it on the fire.
The intermediate limbs and articulations must move accordingly. Now you will code all this... And you fall well inside the domain called the Inverse Kinematics issue, which may demand some horrible calculi, such as the evaluation of the pseudo-inverses of Jacobi matrices, but doesn't matter. You must *reason* differently. The hand "pulls" the elbow, which pulls the arm, which "says": "may dear brain, I need the following commands from you, in order that our terminal effector obey its scenario..." == Folks, this is no science fiction, but *ALL COMPLICATED ANIMATIONS* are done in this way. The IK is an established industrial domain, and in my humble opinion, the laziness IS the tool to code it in a readable manner (I work on this right now, but slowly...) Jerzy Karczmarczuk PS. BTW. The True Real World is quantum, not classical. A bottle of the most expensive champagne I can afford, to a guy who will convince me that the quantum world is strict in the computational sense of this word. In my opinion this category is not applicable at all... _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Nick wrote:
The question is the following: how big the gap between strict languages with lazy constructs and Haskell? Does the default lazyness have irrefutable advantage over default strictness?
Laziness is needed to achieve true compositionality. This point is elaborated in John Hughes. "Why functional programming matters" http://haskell.org/haskellwiki/Research_papers#Overview I also think that the laziness in Haskell is already so implicit that 90% of the Haskell code written so far will simply break irreparably if you experimentally remove it. By the way, lazy evaluation is strictly more powerful than eager evaluation (in a pure language, that is) with respect to asymptotic complexity: Richard Bird, Geraint Jones and Oege de Moor. "More Haste, Less Speed." http://web.comlab.ox.ac.uk/oucl/work/geraint.jones/morehaste.html Regards, apfelmus

apfelmus,
The question is the following: how big the gap between strict languages with lazy constructs and Haskell? Does the default lazyness have irrefutable advantage over default strictness?
Laziness is needed to achieve true compositionality. This point is elaborated in "Why functional programming matters" by John Hughes Yes, I like the paper. But the examples can be just decomposed into generator and the rest, and the generator can be made lazy in case of strict languages. For instance, finding "Newton-Raphson Square Roots" can be expressed in strict language (Scala again):
repeat (f, a) : Stream[Double] = Stream.cons(repeat f (f a)) or in hypothetical language "L" with some syntactic sugar repeat f a = *lazy* cons a (repeat f (f(a)) To be clear, I don't mind against laziness at all, I want to know what I get if I take laziness everywhere as default semantics.
I also think that the laziness in Haskell is already so implicit that 90% of the Haskell code written so far will simply break irreparably if you experimentally remove it.
Yes, I understand, that the present Haskell code heavily bases on laziness, but I'm going into the problem in general: how much I get, if I switch from default strictness to default laziness in my hypothetical language L? Or, from other side, how much I throw away in the reverse case?
By the way, lazy evaluation is strictly more powerful than eager evaluation (in a pure language, that is) with respect to asymptotic complexity:
Richard Bird, Geraint Jones and Oege de Moor. "More Haste, Less Speed." http://web.comlab.ox.ac.uk/oucl/work/geraint.jones/morehaste.html
You gave me a lot of food for thought. Thank you for the link. Best regards, Nick.

Nick, Roughly, I'd say you can fudge laziness in data structures in a strict language without too much bother. (I don't have much experience with this, but the existence of a streams library for OCaml is the sort of thing I mean. There are plenty of papers on co- iterative streams and suchlike that show the general pattern.) If you wish to add control structures you would need to use the lazy keyword a lot, e.g.: if cond then *lazy* S1 else *lazy* S2 and for more complicated structures it's not going to be always clear what needs to be suspended. Laziness is a conservative default here. (If you want to write an EDSL in a non-lazy language, you'll need to use some kind of preprocessor / macros / ... - in other words, a two- level language - or do thunking by hand, as above, or live with doing too much evaluation.) One way to gauge how useful laziness really is might be to look through big ML projects and see how often they introduce thunks manually. A thunk there is usually something like "fn () => ..." IIRC. Also IIRC, Concurrent ML is full of them. Dare I say the tradeoff is between a relatively simple operational model (so you can judge space and time usage easily) and semantic simplicity (e.g. the beta rule is unrestricted, easing program transformation). cheers peter

Someone already mentioned John Hughes paper. Another resource is SPJ's
"hair shirt" slides (also discusses type classes and monads).
http://research.microsoft.com/~simonpj/papers/haskell-retrospective/HaskellR...
Laziness is addressed beginning on slide 19.
Other Nick
On 2/15/07, Nick
Hi all,
(Another topic stolen from a Russian forum discussion).
As everyone know, there are lot of strict languages, that have possibilities to "switch on" lazy evaluation when needed.
But the examples that I saw on Haskell, there was not much use of lazy evaluation, often there were just several lazy points, and the rest could be done strictly without loss of generality. For example, in finding primes:
main = print primes primes = 2:filter is_prime [3,5..] is_prime n = all (\p-> n `mod` p /= 0) (takeWhile (\p-> p*p<=n) primes) We can rewrite this in strict languages with lazy constructs. For example, in Scala (of course stream is not only lazily evaluated thing there) def main(args: Array[String]): Unit = { val n = Integer.parseInt(args(0)) System.out.println(primes(ints(2)) take n toList) }
def primes(nums: Stream[Int]): Stream[Int] = Stream.cons(nums.head, primes ((nums tail) filter (x => x % nums.head != 0)) )
def ints(n: Int): Stream[Int] = Stream.cons(n, ints(n+1))
I think the Haskell solution is more compact due to syntactic sugar, curring and "parentheses-free-ness", *not* lazy evaluation.
According to one guy's analogy: the Real World is strict - in order to drink tea, you have to put the cattle on the fire, wait until water boils, brew tea and then drink. Not the cattle is put on the fire, water boils and the tea is brewed when you take the empty cup to start drinking. :-)
The question is the following: how big the gap between strict languages with lazy constructs and Haskell? Does the default lazyness have irrefutable advantage over default strictness?
Thank you for the attention.
With best regards, Nick.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

So, as I understand, choosing default laziness was just experimental design decision in order to answer the >question: "how good lazy language can be". I am practically convinced, that lazy evaluation included in the >_right_ places can be extremely useful. I didn't state the question as "strict vs lazy", my question is different - >"default laziness with optional strict -vs- default strictness with optional lazy". And sorry, but the question >remains open.
at the time, lazyness was also the best-known basis for pure functional i/o (result continuations and monads taking over later), still a hot and tricky topic then. as for defaults, lazy evaluation is normal order strategy + sharing of arguments, strict evaluation corresponds to applicative order strategy, and we know from lambda-calculus that normal order strategy is normalizing (reaches a normal form if one exists) whereas applicative order strategy is not. on this basis, non-strictness is a safe default, with strictness to be inferred or annotated where needed. since strictness is undecidable in general, inference has to be approximate, and a safe default is essential. of course, one can program in mostly strict languages - I started out in one that used applicative order strategy, but had normal order application as well, plus the usual \()->thunking. and as you say, modern versions of default strictness allow you to annotate the function as non-strict, so you don't have to use special application operators everywhere, and lazy-keywords are clearer than \()->thunks. but from my own experience, I had to think a lot more about evaluation order in the default-strict language than I have to in the default-non-strict language, and what is worse, I had to do this thinking up-front, whereas now I can think about the data-dependencies first, and do the thinking about evaluation order later, and only on demand:-) that is also why programs written in default-strict languages often seem to win in performance competitions: if you get it to work at all, you'll also have put in some thoughts on performance/evaluation order already. programs written in default-non-strict languages can be made to "work" without worrying about those details, so it often happens to look as if lazy programs were resource- hungry, and a lot of extra work had to be put in to make them efficient. but I'd put it differently: about the same amount of thought has to be put in to make either kind of program efficient, only that with non-strict default, I get to choose when (and whether) to put in that effort. in other words, default-strict languages are strict in demanding evaluation- order information early, whereas default-non-strict languages give the programmer more leeway. hth, claus

"Nick":
So, as I understand, choosing default laziness was just experimental design decision in order to answer the question: "how good lazy language can be". I am practically convinced, that lazy evaluation included in the _right_ places can be extremely useful. I didn't state the question as "strict vs lazy", my question is different - "default laziness with optional strict -vs- default strictness with optional lazy".
And sorry, but the question remains open.
=== Now, I AM SORRY, but this is a bit - not wishing to offend, nor to annoy anybody - of a totalitarian philosophy. The world of programming is very rich, you can find the languages and the paradigms you want, and you can always construct new ones. You have strict languages as Scheme or ML, with some possibilities to do lazy programming. Go ahead! (But you will pay a price. The laziness in Scheme introduced by the delay macro can produce a lot of inefficient code, much worse than coded at the base level). The question is NOT open. The question has been answered a long time ago in a liberal manner. You have both. You *choose* your programming approach. You choose your language, if you don't like it, you go elsewhere, or you produce another one, of your own. Haskell chose a particular schema, that implied a *very concrete* decision concerning the underlying abstract machine model, and the implementation. It is a bit frustrating reading over and over the complaints of people who never needed, so they dont appreciate laziness, who want to revert Haskell to strict. As if we were really obliged to live inside of a specific Iron Curtain, where only one paradigm is "legal". == There are other annoying discussions as well. For example, here rather rarely, since it is a dedicated list, but on the newsgroup of FP (which I read rarely) from time to time somebody *must* complain that there is another lazy language, Clean, not too distinct from Haskell, and this seems to be a waste of effort, - the Cleaners should join Haskell, and contribute to its development instead of making another one, redundant project. Eine Kirche, eine Sprache, eine Partei, ein Volk??? Horrible perspective. Jerzy Karczmarczuk

Jerzy Karczmarczuk,
You have strict languages as Scheme or ML, with some possibilities to do lazy programming. Go ahead! (But you will pay a price. The laziness in Scheme introduced by the delay macro can produce a lot of inefficient code, much worse than coded at the base level). Maybe I am not clear enough, but this is the price I try to measure. :-) The question is NOT open. The question has been answered a long time ago in a liberal manner. You have both. You *choose* your programming approach. You choose your language, if you don't like it, you go elsewhere, or you produce another one, of your own. Yes, I agree, the world of programming is very rich. But you probably know, there are quite a few of curious people (at least in the Russian community) that begin to be interested in other (than mainstream) languages. Of course, one moment they meet Haskell, and get exited of its excellent expressive capabilities, but finally ask the same question:
What advantages does lazy language have? And you see, it is incorrect to answer: "Relax, no advantages at all, take a look at ML or Scheme", because it is just not true. But in order to invite new members to the community, we have to answer this question (and plus 100 other boring questions) over and over again. Especially it is even harder to avoid another holy war, because on the other side there are languages with advanced expressiveness features and macrosystem.
Haskell chose a particular schema, that implied a *very concrete* decision concerning the underlying abstract machine model, and the implementation. It is a bit frustrating reading over and over the complaints of people who never needed, so they dont appreciate laziness, who want to revert Haskell to strict. As if we were really obliged to live inside of a specific Iron Curtain, where only one paradigm is "legal". You misunderstood me, I don't try to revert Haskell to strict. I like Haskell as is. My motivation is different.
Best regards, Nick.

Nick wrote:
main = print primes primes = 2:filter is_prime [3,5..] is_prime n = all (\p-> n `mod` p /= 0) (takeWhile (\p-> p*p<=n) primes)
We can rewrite this in strict languages with lazy constructs. For example, in Scala (of course stream is not only lazily evaluated thing there)
def main(args: Array[String]): Unit = { val n = Integer.parseInt(args(0)) System.out.println(primes(ints(2)) take n toList) }
def primes(nums: Stream[Int]): Stream[Int] = Stream.cons(nums.head, primes ((nums tail) filter (x => x % nums.head != 0)) )
def ints(n: Int): Stream[Int] = Stream.cons(n, ints(n+1))
Aha, I finally recovered some of the examples from which the claim "Laziness is needed to achieve true compositionality" stems. The first is already present in your example above and also showed up some time ago in the thread "Optimisation fun". The point is that the function 'all' used in is_prime n = all (\p-> n `mod` p /= 0) (takeWhile (\p-> p*p<=n) primes) works only because we have lazy *Bool*eans. Your Scala version accidentally (?) circumvents it by using a different algorithm, namely primes' = sieve [2..] sieve (x:xs) = x : filter (\y -> y `mod` x /= 0) (sieve xs) Thanks to laziness, 'all' stops as soon as one element does not fulfill the condition. "True compositionality" allows us to define all p = foldr (&&) True . map p and get the lazy behavior. You cannot reuse a strict (&&) in such a way. Of course, given some support for lazy constructs, you could define a lazy version of (&&) just as you define a lazy version of lists (called "Streams"), but not having laziness as default means that you have to think about whether your function is intended to be re-used (=> you have to provide lazy interface) or not *before* you write your function. The second folklore example is lazy mergesort: mergesort [] = [] mergesort xs = foldtree1 merge $ map return xs foldtree1 f [x] = x foldtree1 f xs = foldtree1 f $ pairs xs where pairs [] = [] pairs [x] = [x] pairs (x:x':xs) = f x x' : pairs xs merge [] ys = ys merge xs [] = xs merge (x:xs) (y:ys) = if x <= y then x:merge xs (y:ys) else y:merge (x:xs) ys The point about this 'mergesort' is that while it sorts a complete list in O(N log N) time, it may return the minimum element in O(N) time already. Thus, we can be bold and reuse 'mergesort' as in minimum = head . mergesort and still get the desired O(N) asymptotic complexity. Note: The function 'foldtree' folds the elements of a list as if they where in a binary tree: foldrtree f [1,2,3,4,5,6,7,8] ==> ((1 `f` 2) `f` (3 `f` 4)) `f` ((1 `f` 2) `f` (3 `f` 4)) The O(N) stuff works because 'foldtree' constructs this expression in O(N + N/2 + N/4 + N/8 + ..) = O(N) time. I'm not entirely sure, but I think that the more common 'splitAt (length xs `div` 2)' and 'deal (x:x':xs) = (x:..,x':..)' approaches both take O(N log N) time for the same task. This makes them unusable for the point here. Besides, only 'foldtree' can easily be transformed into a proof for dependent types, but that's another story told by Conor McBride in 'Why dependent types matter'. There has been another example circulating on #haskell. I think it was something with substrings = concatMap tails . inits but I can't remember it now. Cale, can you help? Anyway, the point is that with domain specific embedded languages, the re-usability without time penalties is crucial. So far, only default laziness can achieve this.
I also think that the laziness in Haskell is already so implicit that 90% of the Haskell code written so far will simply break irreparably if you experimentally remove it.
Yes, I understand, that the present Haskell code heavily bases on laziness, but I'm going into the problem in general: how much I get, if I switch from default strictness to default laziness in my hypothetical language L? Or, from other side, how much I throw away in the reverse case?
Yes, what I meant with "laziness in Haskell is already so implicit" is that the re-use I exemplified above happens subconsciously. So indeed, it looks like - and only looks like - one could easily turn a lazy language into a strict one. Isn't that the good thing about laziness that nobody notices it in the code? Regards, apfelmus

apfelmus, Cool! I really like your examples! Thank you. Nick.
participants (12)
-
Allan Clark
-
apfelmus@quantentunnel.de
-
Claus Reinke
-
Dan Weston
-
dons@cse.unsw.edu.au
-
Dougal Stanton
-
Gleb
-
jerzy.karczmarczuk@info.unicaen.fr
-
Kurt Schelfthout
-
Nick
-
Nicolas Frisby
-
Peter Gammie