
Hi all, A while ago there was a discussion on haskell-cafe about the semantics of strict bits in datatypes that never reached a conclusion; I've checked with Malcolm and there is still disagreement about the right answer. The original thread is around here: http://www.haskell.org/pipermail/haskell-cafe/2006-October/018804.html but I will try to give all the relevant information in this message. The question is, given: data Fin a = FinCons a !(Fin a) | FinNil w = let q = FinCons 3 q in case q of FinCons i _ -> i is w 3 or _|_? ---------- The _|_ argument ---------- (Supporters include me, ghc and hugs) q = FinCons 3 q === (by Haskell 98 report 4.2.1/Strictness Flags/Translation q = (FinCons $ 3) $! q === (by definition of $, $!) q = q `seq` FinCons 3 q === (solution is least fixed point of the equation) q = _|_ Thus w = case _|_ of FinCons i _ -> i so w = _|_. ---------- The 3 argument ---------- (Supporters include Malcolm Wallace, nhc98 and yhc) Here I will just quote what Malcolm said in his original message: The definition of seq is seq _|_ b = _|_ seq a b = b, if a/= _|_ In the circular expression let q = FinCons 3 q in q it is clear that the second component of the FinCons constructor is not _|_ (it has at least a FinCons constructor), and therefore it does not matter what its full unfolding is. and in his recent e-mail to me: Yes, I still think this is a reasonable interpretation of the Report. I would phrase it as "After evaluating the constructor expression to WHNF, any strict fields contained in it are also be guaranteed to be in WHNF." This also makes q a fixpoint of q = q `seq` FinCons 3 q, but not the least fixed point. ---------- So I think it would be good if we can all agree on what the meaning should be, and then to clarify the wording in the report so that future readers understand it correctly too. Thanks Ian

Ian Lynagh wrote:
Here I will just quote what Malcolm said in his original message:
The definition of seq is seq _|_ b = _|_ seq a b = b, if a/= _|_
In the circular expression let q = FinCons 3 q in q it is clear that the second component of the FinCons constructor is not _|_ (it has at least a FinCons constructor), and therefore it does not matter what its full unfolding is.
Well, in a sense, it's exactly the defining property of strict constructors that they are not automatically different from _|_. The translation
q = FinCons 3 q === (by Haskell 98 report 4.2.1/Strictness Flags/Translation q = (FinCons $ 3) $! q
is rather subtle: the first FinCons is a strict constructor whereas the second is "the real constructor". In other words, the translation loops as we could (should?) apply FinCons => \x y -> FinCons x $! y => \x y -> (\x' y' -> FinCons x' $! y') x $! y => ... ad infinitum.
and in his recent e-mail to me:
Yes, I still think this is a reasonable interpretation of the Report. I would phrase it as "After evaluating the constructor expression to WHNF, any strict fields contained in it are also be guaranteed to be in WHNF."
Referring to WHNF would break the report's preference of not committing to a particular evaluation strategy. That's already a good reason to stick with FinCons 3 _|_ = _|_. Besides, having let q = FinCons 3 q in q not being _|_ crucially depends on memoization. Even with the characterization by WHNF, let q x = FinCons 3 (q x) in q () is _|_. Regards, apfelmus

apfelmus@quantentunnel.de writes:
Besides, having
let q = FinCons 3 q in q
not being _|_ crucially depends on memoization.
Does it? Mentally I translate that as let q = Y (\q -> FinCons 3 q) in q => Y (\q-> FinCons 3 q) => (\q -> FinCons 3 q) (Y (\q-> FinCons 3 q)) => FinCons 3 (Y (\q -> FinCons 3 q)) which, assuming a plausible lambda expression for FinCons, is a soluble term.
Even with the characterization by WHNF,
let q x = FinCons 3 (q x) in q ()
is _|_.
Again q = Y(\q x -> FinCons 3 (q x)) so q () => Y(\q x -> FinCons 3 (q x)) () => (\q x -> FinCons 3 (q x))(Y(\q x -> FinCons 3 (q x))) () => (\x -> FinCons 3 (Y(\q y-> FinCons 3 (q y)) x)) () => FinCons 3 (Y(\q x -> FinCons 3 (q x)) () ) which is in WHNF (and soluble too) -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

On Fri, Mar 16, 2007 at 05:00:15PM +0000, Jón Fairbairn wrote:
Does it? Mentally I translate that as
let q = Y (\q -> FinCons 3 q) in q
but it would actually translate to
let q = Y (\q -> q `seq` FinCons 3 q) in q
for strict fields, whenever a constructor appears, it is translated to one which seq's its strict fields before creating the constructor. so, FinCons 3 q desugars to q `seq` FinCons 3 q wherever it appears, strict fields have no effect on deconstructing data types. John -- John Meacham - ⑆repetae.net⑆john⑈

| FinCons 3 q | desugars to | | q `seq` FinCons 3 q wherever it appears, | | strict fields have no effect on deconstructing data types. That's GHC's behaviour too. I think it's the right one too! (It's certainly easy to explain.) Simon

Simon Peyton-Jones wrote:
| strict fields have no effect on deconstructing data types.
That's GHC's behaviour too. I think it's the right one too! (It's certainly easy to explain.)
This reminds me of something I discovered about using strict fields in AVL trees (with ghc). Using strict fields results in slower code than doing the `seq` desugaring by hand. If I have.. data AVL e = E | N !(AVL e) e !(AVL e) .. etc then presumably this.. case avl of N l e r -> N (f l) e r desugars to something like .. case avl of N l e r -> let l' = f l in l' `seq` r `seq` N l' e r but IMO it should desugar to.. case avl of N l e r -> let l' = f l in l' `seq` N l' e r which is what I ended up writing by hand all over the place (dropping the strictness annotation in the data type). That is, variables that have been obtained by matching strict fields (r in the case) should not be re-seqed if they are re-used in another strict context. Now this explanation for the slow down I observed is just speculation on my part (I don't actually know what ghc or any other compiler does). But on modern memory architectures, forcing the code to inspect heap records that it shouldn't have to inspect will be a bad thing. So semantically I agree with "strict fields have no effect on deconstructing data types", but they should have an effect on the code that an optimising compiler generates IMO. Regards -- Adrian Hey

| This reminds me of something I discovered about using strict fields in | AVL trees (with ghc). Using strict fields results in slower code than | doing the `seq` desugaring by hand. That is bad. Can you send a test case that demonstrates this behaviour? | If I have.. | | data AVL e = E | | N !(AVL e) e !(AVL e) | .. etc | | then presumably this.. | | case avl of N l e r -> N (f l) e r | | desugars to something like .. | | case avl of N l e r -> let l' = f l | in l' `seq` r `seq` N l' e r | | but IMO it should desugar to.. | | case avl of N l e r -> let l' = f l | in l' `seq` N l' e r I agree. If it doesn't please let me know! Simon

Simon Peyton-Jones wrote:
| This reminds me of something I discovered about using strict fields in | AVL trees (with ghc). Using strict fields results in slower code than | doing the `seq` desugaring by hand.
That is bad. Can you send a test case that demonstrates this behaviour?
OK, I'll try to put something reasonably simple together to test this again. Last time I tested it was a probably a couple of years ago so what I said might not be true of current ghc. The effect wasn't huge in any case (using strict constructors was about 5% slower). Regards -- Adrian Hey

On Mon, Mar 19, 2007 at 03:22:29PM +0000, Simon Peyton-Jones wrote:
| This reminds me of something I discovered about using strict fields in | AVL trees (with ghc). Using strict fields results in slower code than | doing the `seq` desugaring by hand.
That is bad. Can you send a test case that demonstrates this behaviour?
| If I have.. | | data AVL e = E | | N !(AVL e) e !(AVL e) | .. etc | | then presumably this.. | | case avl of N l e r -> N (f l) e r | | desugars to something like .. | | case avl of N l e r -> let l' = f l | in l' `seq` r `seq` N l' e r | | but IMO it should desugar to.. | | case avl of N l e r -> let l' = f l | in l' `seq` N l' e r
I agree. If it doesn't please let me know!
Although I have not looked into this much, My guess is it is an issue in the simplifier, normally when something is examined with a case statement, the simplification context sets its status to 'NoneOf []', which means we know it is in WHNF, but we don't have any more info about it. I would think that the solution would be to add the same annotation in the simplifier to variables bound by pattern matching on strict data types? Just a theory. I am not sure how to debug this in ghc without digging into it's code. John -- John Meacham - ⑆repetae.net⑆john⑈

| Although I have not looked into this much, My guess is it is an issue in | the simplifier, normally when something is examined with a case | statement, the simplification context sets its status to 'NoneOf []', | which means we know it is in WHNF, but we don't have any more info about | it. I would think that the solution would be to add the same annotation | in the simplifier to variables bound by pattern matching on strict data | types? Indeed! GHC already does this. That's why I am surprised that adding seq improves things. Adrian has helpfully sent a test case, but I have not examined it yet S

Jón Fairbairn wrote:
apfelmus@quantentunnel.de writes:
Besides, having
let q = FinCons 3 q in q
not being _|_ crucially depends on memoization.
Does it?
Sorry for having introduced an extra paragraph, I meant that q =/= _|_ under the new WHNF-rule would depend on memoization. At the memory location of q, hereby marked with *q, evaluation would yield *q: q => *q: FinCons 3 q Now, this can be considered "ok" according to the rule because the data at the location is WHNF and the second argument of FinsCons is WHNF as well because we just evaluated q to WHNF. By introducing an extra parameter, the memoization is gone and evaluation will yield q () => FinCons 3 (q ()) The point is that the second argument to FinCons is not WHNF, so we have to evaluate that further in order to generate only values that conform to the new WHNF-rule. Of course, this evaluation will diverge now. With the above, I want to show that the proposed new WHNF-rule gives non-_|_ values in very special cases only. I don't think that these are worth it. Regards, apfelmus PS: Your derivations are fine in the case of a non-strict FinCons. But the point is to make in strict.

apfelmus@quantentunnel.de writes:
apfelmus@quantentunnel.de writes:
Besides, having
let q = FinCons 3 q in q
not being _|_ crucially depends on memoization.
Does it? PS: Your derivations are fine in the case of a non-strict FinCons. But
Jón Fairbairn wrote: the point is to make in strict.
Yes, I was trying to be subtle but was too sleepy and lost the plot. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

On Fri, Mar 16, 2007 at 05:40:17PM +0100, apfelmus@quantentunnel.de wrote:
The translation
q = FinCons 3 q === (by Haskell 98 report 4.2.1/Strictness Flags/Translation q = (FinCons $ 3) $! q
is rather subtle: the first FinCons is a strict constructor whereas the second is "the real constructor". In other words, the translation loops as we could (should?) apply
FinCons => \x y -> FinCons x $! y => \x y -> (\x' y' -> FinCons x' $! y') x $! y => ...
ad infinitum.
Yes, perhaps that ought to be fixed. But even so, this clearly implies that FinCons 3 _|_ = _|_ and thus that q is _|_ and nhc98/yhc have a bug.

Hello,
I also think that the first version is the correct one (i.e., the
result is _|_).
-Iavor
On 3/16/07, Ross Paterson
On Fri, Mar 16, 2007 at 05:40:17PM +0100, apfelmus@quantentunnel.de wrote:
The translation
q = FinCons 3 q === (by Haskell 98 report 4.2.1/Strictness Flags/Translation q = (FinCons $ 3) $! q
is rather subtle: the first FinCons is a strict constructor whereas the second is "the real constructor". In other words, the translation loops as we could (should?) apply
FinCons => \x y -> FinCons x $! y => \x y -> (\x' y' -> FinCons x' $! y') x $! y => ...
ad infinitum.
Yes, perhaps that ought to be fixed. But even so, this clearly implies that
FinCons 3 _|_ = _|_
and thus that q is _|_ and nhc98/yhc have a bug.
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

Ross Paterson wrote:
On Fri, Mar 16, 2007 at 05:40:17PM +0100, apfelmus wrote:
the translation loops as we could (should?) apply
FinCons => \x y -> FinCons x $! y => \x y -> (\x' y' -> FinCons x' $! y') x $! y => ...
ad infinitum.
Yes, perhaps that ought to be fixed. But even so, this clearly implies that
FinCons 3 _|_ = _|_
and thus that q is _|_ and nhc98/yhc have a bug.
Yes, I agree completely. I should have separated the observation that the rewrite rule for the translation of strict constructors loops from the business with q. Regards, apfelmus

Given the translation of strict constructors I can't anything but _|_ as the answer. On Mar 16, 2007, at 15:50 , Ian Lynagh wrote:
Hi all,
A while ago there was a discussion on haskell-cafe about the semantics of strict bits in datatypes that never reached a conclusion; I've checked with Malcolm and there is still disagreement about the right answer. The original thread is around here: http://www.haskell.org/pipermail/haskell-cafe/2006-October/018804.html but I will try to give all the relevant information in this message.
The question is, given:
data Fin a = FinCons a !(Fin a) | FinNil
w = let q = FinCons 3 q in case q of FinCons i _ -> i
is w 3 or _|_?
---------- The _|_ argument ----------
(Supporters include me, ghc and hugs)
q = FinCons 3 q === (by Haskell 98 report 4.2.1/Strictness Flags/Translation q = (FinCons $ 3) $! q === (by definition of $, $!) q = q `seq` FinCons 3 q === (solution is least fixed point of the equation) q = _|_
Thus
w = case _|_ of FinCons i _ -> i
so w = _|_.
---------- The 3 argument ----------
(Supporters include Malcolm Wallace, nhc98 and yhc)
Here I will just quote what Malcolm said in his original message:
The definition of seq is seq _|_ b = _|_ seq a b = b, if a/= _|_
In the circular expression let q = FinCons 3 q in q it is clear that the second component of the FinCons constructor is not _|_ (it has at least a FinCons constructor), and therefore it does not matter what its full unfolding is.
and in his recent e-mail to me:
Yes, I still think this is a reasonable interpretation of the Report. I would phrase it as "After evaluating the constructor expression to WHNF, any strict fields contained in it are also be guaranteed to be in WHNF."
This also makes q a fixpoint of q = q `seq` FinCons 3 q, but not the least fixed point.
----------
So I think it would be good if we can all agree on what the meaning should be, and then to clarify the wording in the report so that future readers understand it correctly too.
Thanks Ian
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

Ian Lynagh
data Fin a = FinCons a !(Fin a) | FinNil w = let q = FinCons 3 q in case q of FinCons i _ -> i
is w 3 or _|_?
Knowing that opinions seem to be heavily stacked against my interpretation, nevertheless I'd like to try one more attempt at persuasion. The Haskell Report's definition of `seq` does _not_ imply an order of evaluation. Rather, it is a strictness annotation. (Whether this is the right thing to do is another cause of dissent, but let's accept the Report as is for now.) So `seq` merely gives a hint to the compiler that the value of its first argument must be established to be non-bottom, by the time that its second argument is examined by the calling context. The compiler is free to implement that guarantee in any way it pleases. So just as, in the expression x `seq` x one can immediately see that, if the second x is demanded, then the first one is also demanded, thus the `seq` can be elided - it is semantically identical to simply x Now, in the definition x = x `seq` foo one can also make the argument that, if the value of x (on the lhs of the defn) is demanded, then of course the x on the rhs of the defn is also demanded. There is no need for the `seq` here either. Semantically, the definition is equivalent to x = foo I am arguing that, as a general rule, eliding the `seq` in such a case is an entirely valid and correct transformation. The objection to this point of view is that if you have a definition x = x `seq` foo then, operationally, you have a loop, because to evaluate x, one must first evaluate x before evaluating foo. But as I said at the beginning, `seq` does _not_ imply order of evaluation, so the objection is not well-founded. Regards, Malcolm

On Mar 20, 2007, at 9:53 AM, Malcolm Wallace wrote:
Ian Lynagh
wrote: data Fin a = FinCons a !(Fin a) | FinNil w = let q = FinCons 3 q in case q of FinCons i _ -> i
is w 3 or _|_?
Knowing that opinions seem to be heavily stacked against my interpretation, nevertheless I'd like to try one more attempt at persuasion.
The Haskell Report's definition of `seq` does _not_ imply an order of evaluation. Rather, it is a strictness annotation. (Whether this is the right thing to do is another cause of dissent, but let's accept the Report as is for now.) So `seq` merely gives a hint to the compiler that the value of its first argument must be established to be non-bottom, by the time that its second argument is examined by the calling context. The compiler is free to implement that guarantee in any way it pleases.
So just as, in the expression x `seq` x one can immediately see that, if the second x is demanded, then the first one is also demanded, thus the `seq` can be elided - it is semantically identical to simply x
Now, in the definition x = x `seq` foo one can also make the argument that, if the value of x (on the lhs of the defn) is demanded, then of course the x on the rhs of the defn is also demanded. There is no need for the `seq` here either. Semantically, the definition is equivalent to x = foo I am arguing that, as a general rule, eliding the `seq` in such a case is an entirely valid and correct transformation.
The objection to this point of view is that if you have a definition x = x `seq` foo then, operationally, you have a loop, because to evaluate x, one must first evaluate x before evaluating foo. But as I said at the beginning, `seq` does _not_ imply order of evaluation, so the objection is not well-founded.
I just want to say that the argument I find most convincing is the 'least fixpoint' argument, which does not at all require assumptions about order of evaluation. I see your arguments as something along the lines "the non-bottom answer is a fixpoint of the equations, and therefore it is the correct answer". And, it is in fact _a_ fixpoint; but it is not the _least_ fixpoint, which would be bottom. To recap, the equation in question is: q = seq q (RealFinCons 3 q) It is not hard to see that q := _|_ is a fixpoint. Also, we have that q := LUB( _|_, RealFinCons 3 _|_, RealFinCons 3 (RealFinCons 3 _|_), ... ) is a fixpoint and is <> _|_. But that doesn't matter since _|_ is the least element of the domain and must therefore be the least fixpoint.
Regards, Malcolm
Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG

On Tue, Mar 20, 2007 at 01:53:47PM +0000, Malcolm Wallace wrote:
Now, in the definition x = x `seq` foo one can also make the argument that, if the value of x (on the lhs of the defn) is demanded, then of course the x on the rhs of the defn is also demanded. There is no need for the `seq` here either. Semantically, the definition is equivalent to x = foo I am arguing that, as a general rule, eliding the `seq` in such a case is an entirely valid and correct transformation.
So does nhc98 print "Foo" for this program? main = putStrLn $ let x = x `seq` "Foo" in x (yhc tells me my program has deadlocked, but my recent attempt to compile nhc98 failed so I can't check it). I don't fully understand what your interpretation is; is it also true that y = x x = y `seq` foo is equivalent to y = x x = foo ? And is it true that y = if True then x else undefined x = y `seq` foo is equivalent to y = x x = foo ?
The objection to this point of view is that if you have a definition x = x `seq` foo then, operationally, you have a loop, because to evaluate x, one must first evaluate x before evaluating foo. But as I said at the beginning, `seq` does _not_ imply order of evaluation, so the objection is not well-founded.
I'm having trouble finding a non-operational description of the behaviour I think seq should have. (Nor, for that matter, can I think of a description that makes it clear that it has the semantics that you think it should have). Anyone? I think you could make a similar argument that let x = x in x :: () is () rather than _|_, and similarly let x = x in x :: Int is 3, or is there some key difference I'm missing? Thanks Ian

Malcolm wrote:
The Haskell Report's definition of `seq` does _not_ imply an order of evaluation. Rather, it is a strictness annotation.
That is an important point.
Now, in the definition x = x `seq` foo one can also make the argument that, if the value of x (on the lhs of the defn) is demanded, then of course the x on the rhs of the defn is also demanded. There is no need for the `seq` here either. Semantically, the definition is equivalent to x = foo I am arguing that, as a general rule, eliding the `seq` in such a case is an entirely valid and correct transformation.
I think it is possible that both camps are right on this issue, as far as Haskell 98 stands. We can translate the definition of x into: x = fix (\y -> seq y foo) Isn't it the case that, denotationally, _|_ and foo are valid interpretations of the rhs? If we want to choose between them then we need something extra, such as an operational semantics, or a rule saying that we prefer the least solution. Perhaps I am just re-stating what Ian wrote in the beginning :) Cheers, Bernie.

On Tue, 20 Mar 2007, "Bernie Pope"
Malcolm wrote:
x = x `seq` foo
We can translate the definition of x into:
x = fix (\y -> seq y foo)
Isn't it the case that, denotationally, _|_ and foo are valid interpretations of the rhs?
If we want to choose between them then we need something extra, such as an operational semantics, or a rule saying that we prefer the least solution.
We already have such a rule. According to the H98 report the let expression let x = x `seq` foo in ... can be translated into let x = fix (\~y -> y `seq` foo) in ... where "fix is the least fixpoint operator". Now, since seq ⊥ x = ⊥ we get that ⊥ is the least fixpoint of (\~y -> y `seq` foo), so the above _is_ equivalent to let x = ⊥ in ... (If x is also, by some other reading of the report, equivalent to some non-bottom expression, then the report should be fixed.) -- /NAD

x `seq` x === x and so x = x `seq` x === x = x but, in general, x = x `seq` foo =/= x = foo consider x = x `seq` ((1:) x) x = x `seq` ((1:) (x `seq` ((1:) x))) x = x `seq` ((1:) (x `seq` ((1:) (x `seq` ((1:) x))))) .. ignoring evaluation order, partially unrolling/substituting x also unrolls/substitutes applications of seq (in proper call-by-need, we couldn't even do the substitution until after the evaluation, so we'd never get this far). no part of the right-hand side is defined unless x is - that is what seq is about, isn't it? i do like the argument about different fixpoints - does that correspond to inductive vs coinductive definitions which are so often mixed in haskell? when working with cyclic structures, we often are quite happy without a base case. so instead of the inductive f 0 = True f n = f (n-1) -- provided that (f (n-1)) is defined, (f n) is defined we have things like nats = 1:map (+1) nats -- nats is partially defined if we just assume that nats is partially defined and it is nice to have both available, if not all that well separated. whether we're talking co-recursion or recursion seems to depend entirely on whether the recursive references are in a non-strict or strict context (so that the definitions are productive or not). so it seems to me that adding seq to a (co-)recursion is precisely about resolving this ambiguity and forcing induction nats = (1:) $! map (+1) nats -- nats is defined if we can prove that nats is defined, which we can't anymore and saying that we can get back to co-induction by eliding the seq may be correct, but irrelevant. and the same reasoning ought to apply to strict fields in data constructors. sorry for waving about precisely defined terms in such a naive manner. i hope it helps, and isn't too far of the mark!-) claus

So we have an equation x = seq x foo In Haskell recursive equations are solved and you get the smallest fix point. The smallest solution to this equation is x = _|_, there are other solutions, but why should we deviate from giving the smallest fix point for seq when we do it for everything else? -- Lennart On Mar 20, 2007, at 13:53 , Malcolm Wallace wrote:
Ian Lynagh
wrote: data Fin a = FinCons a !(Fin a) | FinNil w = let q = FinCons 3 q in case q of FinCons i _ -> i
is w 3 or _|_?
Knowing that opinions seem to be heavily stacked against my interpretation, nevertheless I'd like to try one more attempt at persuasion.
The Haskell Report's definition of `seq` does _not_ imply an order of evaluation. Rather, it is a strictness annotation. (Whether this is the right thing to do is another cause of dissent, but let's accept the Report as is for now.) So `seq` merely gives a hint to the compiler that the value of its first argument must be established to be non-bottom, by the time that its second argument is examined by the calling context. The compiler is free to implement that guarantee in any way it pleases.
So just as, in the expression x `seq` x one can immediately see that, if the second x is demanded, then the first one is also demanded, thus the `seq` can be elided - it is semantically identical to simply x
Now, in the definition x = x `seq` foo one can also make the argument that, if the value of x (on the lhs of the defn) is demanded, then of course the x on the rhs of the defn is also demanded. There is no need for the `seq` here either. Semantically, the definition is equivalent to x = foo I am arguing that, as a general rule, eliding the `seq` in such a case is an entirely valid and correct transformation.
The objection to this point of view is that if you have a definition x = x `seq` foo then, operationally, you have a loop, because to evaluate x, one must first evaluate x before evaluating foo. But as I said at the beginning, `seq` does _not_ imply order of evaluation, so the objection is not well-founded.
Regards, Malcolm _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

On Tue, Mar 20, 2007 at 01:53:47PM +0000, Malcolm Wallace wrote:
Now, in the definition x = x `seq` foo one can also make the argument that, if the value of x (on the lhs of the defn) is demanded, then of course the x on the rhs of the defn is also demanded. There is no need for the `seq` here either. Semantically, the definition is equivalent to x = foo I am arguing that, as a general rule, eliding the `seq` in such a case is an entirely valid and correct transformation.
You're talking about demand, WHNF, etc, but the Report doesn't; it gives a simple denotational semantics for seq and recursive definitions, according to which the first definition is equivalent to x = _|_.
participants (14)
-
Adrian Hey
-
apfelmus@quantentunnel.de
-
Bernie Pope
-
Claus Reinke
-
Ian Lynagh
-
Iavor Diatchki
-
John Meacham
-
Jón Fairbairn
-
Lennart Augustsson
-
Malcolm Wallace
-
Nils Anders Danielsson
-
Robert Dockins
-
Ross Paterson
-
Simon Peyton-Jones