
I just noticed, thanks to some testing of the parallelism support in 6.6 by Satnam Singh, that Control.Parallel exports seq when in fact it should probably export pseq. The difference is subtle. The semantics of seq and pseq are identical; however, GHC can see that seq is strict in both its arguments and hence could choose to evaluate them in either order, whereas pseq is only strict in its first argument as far as the strictness analyser is concerned. The point is that pseq is useful for controlling evaluation order, which is what you want for adding parallelism to a program. seq, on the other hand, is not useful for controlling evaluation order. The documentation in 6.6 is also incorrect on this point. pseq is currently not exported by Control.Parallel, this is an oversight on my part, you have to import it from GHC.Conc for now. For 6.8 we'll export pseq from Control.Parallel instead of seq. Incedentally, the fixity of par is also wrong in 6.6: it should be infixr 0, but in fact it has the default fixity of infixl 0. This means if you write an expression like 'x `par` y `seq` z', it isn't doing what you think. Workaround: either use parentheses, or define your own par with the right fixity. Cheers, Simon

Simon Marlow
The difference is subtle. The semantics of seq and pseq are identical; however, GHC can see that seq is strict in both its arguments and hence could choose to evaluate them in either order, whereas pseq is only strict in its first argument as far as the strictness analyser is concerned. The point is that pseq is useful for controlling evaluation order, which is what you want for adding parallelism to a program. seq, on the other hand, is not useful for controlling evaluation order.
This is a rather weird thing, and I would consider it a bug in the Haskell Report, rather than a bug in ghc. (It bites hard when you are trying to implement something like HPC.) The very name 'seq' surely suggests that you are controlling the evaluation order. "Please evaluate this thing on the left first". But that is _not_ what the Haskell Report says! Ghc takes the Report literally, and so the thing on the right is just as likely to be evaluated before the thing on the left! Surely the language designers did not intend this consequence. For Haskell-prime, can we fix this bug, and ensure that 'seq' really implies ordering of evaluation? [ If you just want strictness annotations, with the compiler free to reorder computations, I would say ($!) is a better bet, and could be redefined to use not the natural `seq`, but the strict-in-both-arguments variation. ] Regards, Malcolm

Malcolm Wallace wrote:
Simon Marlow
wrote: The difference is subtle. The semantics of seq and pseq are identical; however, GHC can see that seq is strict in both its arguments and hence could choose to evaluate them in either order, whereas pseq is only strict in its first argument as far as the strictness analyser is concerned. The point is that pseq is useful for controlling evaluation order, which is what you want for adding parallelism to a program. seq, on the other hand, is not useful for controlling evaluation order.
This is a rather weird thing, and I would consider it a bug in the Haskell Report, rather than a bug in ghc. (It bites hard when you are trying to implement something like HPC.)
The very name 'seq' surely suggests that you are controlling the evaluation order. "Please evaluate this thing on the left first". But that is _not_ what the Haskell Report says! Ghc takes the Report literally, and so the thing on the right is just as likely to be evaluated before the thing on the left!
The report is in general very careful to say absolutely *nothing* about evaluation order, leaving the implementation free to choose, either at compile time or possibly even runtime. This is an important principle, and something I feel quite strongly should be kept at the front of our minds for Haskell Prime. If it isn't already mentioned explicitly in the Haskell 98 report, I think it should be. Incedentally, this is also one reason I think lazy I/O is a wart (despite its obvious usefulness): because it necessarily requires talking about evaluation order. However, having said all that, arguably an exception should be made in this case. The main use of seq (and strictness annotations) is to control operational behaviour, rather than to change the semantics of the program - for example, it is most often used to prevent space leaks by "evaluating something earlier than it would otherwise be" (inverted commas because this isn't currently what seq actually does, as pointed out above). Indeed, if GHC was in the habit of causing the second argument of seq to be evaluated before the first, then a lot of people would probably be surprised. eg. imagine what happens to foldl': foldl' f a [] = a foldl' f a (x:xs) = let a' = f a x in a' `seq` foldl' f a' xs It wouldn't do what you want at all. So I'm agreeing with Malcolm, except that I believe that the evaluation-order property of seq should be a strong hint, not a requirement - otherwise we fall into the trap of mandating evaluation order. Cheers, Simon

Simon Marlow
The report is in general very careful to say absolutely *nothing* about evaluation order, leaving the implementation free to choose,
Yes, this is a highly desirable goal.
However, having said all that, arguably an exception should be made in this case. The main use of seq (and strictness annotations) is to control operational behaviour, rather than to change the semantics of the program
Indeed, `seq` is widely viewed as a wart on the language _because_ it specifies the evaluation order, which is something otherwise avoided in the Report. So the doubly bizarre thing is that, actually, `seq` does not control the evaluation order (which is the only valid reason for wanting to use it in the first place), but nevertheless it undesirably changes the semantics of programs such that equational reasoning no longer holds. I think if we are going to allow ourselves the luxury of semantic breakage, it should at least be worth the cost - we should get some real and definite operational control in return. That is why I think this:
the evaluation-order property of seq should be a strong hint, not a requirement - otherwise we fall into the trap of mandating evaluation order.
is not strong enough. `seq` should guarantee sequential evaluation. If you want a strong (but not mandatory) hint to the compiler about strictness, than that should be a different construct at the user level. At the moment, these alternatives are named `pseq` and `seq`. One suggestion is just to reverse their sense. Another is to use bang patterns for hints. Another might be to introduce strictness hints in type signatures. Regards, Malcolm

Malcolm Wallace wrote:
Indeed, `seq` is widely viewed as a wart on the language _because_ it specifies the evaluation order, which is something otherwise avoided in the Report.
I don't agree with that statement - the main problem with (polymorphic) seq is that its existence implies that the function type is lifted, which has wide-ranging ramifications.
So the doubly bizarre thing is that, actually, `seq` does not control the evaluation order (which is the only valid reason for wanting to use it in the first place), but nevertheless it undesirably changes the semantics of programs such that equational reasoning no longer holds.
I think if we are going to allow ourselves the luxury of semantic breakage, it should at least be worth the cost - we should get some real and definite operational control in return.
That is why I think this:
the evaluation-order property of seq should be a strong hint, not a requirement - otherwise we fall into the trap of mandating evaluation order.
is not strong enough. `seq` should guarantee sequential evaluation. If you want a strong (but not mandatory) hint to the compiler about strictness, than that should be a different construct at the user level.
Not "strictness" - seq already provides that, we're talking about an operational property, that the language definition otherwise does not specify (I just want to be clear about terminology). GHC currently has seq and pseq; pseq guarantees sequential evaluation, seq does not. You want seq to have the pseq behaviour, and to specify this in the report (somehow - lacking any framework to describe operational properties this could only be an informal statement). This would have some undesirable consequences. In an expression like 'a `seq` b `seq` c', I bet in most cases the programmer would be happy for a and b to be evaluated in parallel, but you would require them to be evaluated in strict sequence. What's more, given this expression, the strictness analyser would only be able to infer that 'a' was used strictly, because if it also inferred b and c as strict then the simplifier might reorder the evaluations (normally reordering the evaluation of arguments to a strict function is perfectly ok). So lots of uses of seq to add strictness for performance would simply not work. Forcing seq to evaluate its arguments in strict sequence would be a really bad idea. For those (few) times when you really do want sequential ordering, for controlling parallelism, then we need pseq (call it something else if you want, I'm not fussy about names). Cheers, Simon

On Mon, Nov 06, 2006 at 01:53:52PM +0000, Malcolm Wallace wrote:
So the doubly bizarre thing is that, actually, `seq` does not control the evaluation order (which is the only valid reason for wanting to use it in the first place), but nevertheless it undesirably changes the semantics of programs such that equational reasoning no longer holds.
When I've used seq, it's to ensure that a function is strict in that argument, and therefore has been evaluated before the function is called. (If the language had unlifted types, I might have used those instead). Beyond that, I don't care exactly when it was evaluated; it might be long before, thanks to propagation of strictness information. seq has a clear denotational semantics. One can still do equational reasoning with it, though there will be side conditions about whether something is _|_ or not. The downside is that the eta rules get such side conditions, and polymorphic seq greatly weakens parametricity. Apart from that, the only thing wrong with seq is its name.

Ross Paterson
When I've used seq, it's to ensure that a function is strict in that argument, and therefore has been evaluated before the function is called. (If the language had unlifted types, I might have used those instead). Beyond that, I don't care exactly when it was evaluated; it might be long before, thanks to propagation of strictness information.
When I use `seq`, it is sometimes in a construction like unsafePerformIO (emit "squawk!) `seq` x where I am trying to force the impure side-effect to happen, exactly and immediately before x is evaluated. Whilst this is not good style in a general sense, I argue that it is perfectly safe inside certain kinds of library (e.g. for calculating coverage information, or for emitting tracing information). But if the language itself cannot guarantee this exact placement of side-effects, then it becomes impossible to write computation-reflective tools like Hat and hpc for Haskell, in Haskell. That would surely be a sad state of affairs. Regards, Malcolm

On Mon, Nov 06, 2006 at 06:25:48PM +0000, Malcolm Wallace wrote:
When I use `seq`, it is sometimes in a construction like
unsafePerformIO (emit "squawk!) `seq` x
where I am trying to force the impure side-effect to happen, exactly and immediately before x is evaluated. Whilst this is not good style in a general sense, I argue that it is perfectly safe inside certain kinds of library (e.g. for calculating coverage information, or for emitting tracing information). But if the language itself cannot guarantee this exact placement of side-effects, then it becomes impossible to write computation-reflective tools like Hat and hpc for Haskell, in Haskell. That would surely be a sad state of affairs.
Without admitting the existence of "unsafePerformIO", I submit unsafePerformIO (emit "squawk! >> return x) where >> really does imply sequencing.

Ross Paterson wrote:
On Mon, Nov 06, 2006 at 06:25:48PM +0000, Malcolm Wallace wrote:
When I use `seq`, it is sometimes in a construction like
unsafePerformIO (emit "squawk!) `seq` x
where I am trying to force the impure side-effect to happen, exactly and immediately before x is evaluated. Whilst this is not good style in a general sense, I argue that it is perfectly safe inside certain kinds of library (e.g. for calculating coverage information, or for emitting tracing information). But if the language itself cannot guarantee this exact placement of side-effects, then it becomes impossible to write computation-reflective tools like Hat and hpc for Haskell, in Haskell. That would surely be a sad state of affairs.
Without admitting the existence of "unsafePerformIO", I submit
unsafePerformIO (emit "squawk! >> return x)
where >> really does imply sequencing.
Does it? What's stopping a Haskell implementation from evaluating x early? As far as I know, the only time it wouldn't be valid is if x refers to a stream created by hGetContents, and even then you could evaluate it early as long as you don't move it past some I/O operation that could "tell the difference" (although the report doesn't really say this explicitly, it's just the accepted behaviour of lazy input streams). Cheers, Simon

Malcolm Wallace wrote:
Ross Paterson
wrote: When I've used seq, it's to ensure that a function is strict in that argument, and therefore has been evaluated before the function is called. (If the language had unlifted types, I might have used those instead). Beyond that, I don't care exactly when it was evaluated; it might be long before, thanks to propagation of strictness information.
When I use `seq`, it is sometimes in a construction like
unsafePerformIO (emit "squawk!) `seq` x
where I am trying to force the impure side-effect to happen, exactly and immediately before x is evaluated. Whilst this is not good style in a general sense, I argue that it is perfectly safe inside certain kinds of library (e.g. for calculating coverage information, or for emitting tracing information). But if the language itself cannot guarantee this exact placement of side-effects, then it becomes impossible to write computation-reflective tools like Hat and hpc for Haskell, in Haskell. That would surely be a sad state of affairs.
My take on this kind of thing is that if you want a specific operational behaviour, then you're doing something implementation-specific. We shouldn't mandate any kind of operational behaviour across Haskell implementations. Yes, I'm saying you can't do this portably, and it is good that you can't, becauuse it gives implementations more flexibility. Cheers, Simon

Simon Marlow
When I use `seq`, it is sometimes in a construction like
unsafePerformIO (emit "squawk!) `seq` x
My take on this kind of thing is that if you want a specific operational behaviour, then you're doing something implementation-specific. We shouldn't mandate any kind of operational behaviour across Haskell implementations. Yes, I'm saying you can't do this portably, and it is good that you can't, because it gives implementations more flexibility.
Hmmm. I absolutely agree with the general point that Haskell should, as much as possible, not mandate any specific operational behaviour. But what if I want to _observe_ or record the actual operational behaviour of some particular implementation? For instance, to generate a heap profile, or a computational trace, or a coverage log, or something. The results may well be different for every different implementation, and I am perfectly happy with that. I may actually want to see the differences. But do you really want to say "The Haskell language provides the programmer no mechanism to observe this"? "Use some other language, or some compiler-specific hack"? To me, it is unacceptable to be prevented from write an observational tool for a language in the language itself. Especially since we already have a couple of features in the language that _do_ affect the operational behaviour. They are warts, yes, but if we have to have them, I want them to be genuinely useful. We should bite the bullet and specify in what way they affect the operational semantics, without implying any more specific operational behaviour elsewhere in the language. Regards, Malcolm P.S. Actually, as Ross points out, there is an implied operational semantics of the I/O monad. Maybe that is where the Report needs to become more specific, and mandate certain behaviours.

Malcolm Wallace wrote:
Simon Marlow
wrote: When I use `seq`, it is sometimes in a construction like
unsafePerformIO (emit "squawk!) `seq` x
My take on this kind of thing is that if you want a specific operational behaviour, then you're doing something implementation-specific. We shouldn't mandate any kind of operational behaviour across Haskell implementations. Yes, I'm saying you can't do this portably, and it is good that you can't, because it gives implementations more flexibility.
Hmmm. I absolutely agree with the general point that Haskell should, as much as possible, not mandate any specific operational behaviour. But what if I want to _observe_ or record the actual operational behaviour of some particular implementation? For instance, to generate a heap profile, or a computational trace, or a coverage log, or something. The results may well be different for every different implementation, and I am perfectly happy with that. I may actually want to see the differences. But do you really want to say "The Haskell language provides the programmer no mechanism to observe this"? "Use some other language, or some compiler-specific hack"? To me, it is unacceptable to be prevented from write an observational tool for a language in the language itself.
Yes, I'm saying you have to do something compiler-specific in order to observe the operational behaviour. Now that may well be unsafePerformIO+seq on compiler X, but the point is that this isn't guaranteed to do what you want on all implementations, precisely because we want to admit different evaluation strategies. What does it even *mean* to "evaluate x before y"? For example, we might have an evaluation strategy that uses spare CPUs to search for unevaluated objects in the heap and speculatively evaluate them for a while; we might thereby evaluate y (or some of y's free variables) at any time, and even revert y from an evaluated to an unevaluated state. By even saying that there's a concept of "evaluation order" you've already nailed too many doors shut, IMO.
Especially since we already have a couple of features in the language that _do_ affect the operational behaviour.
what are you referring to specifically? hGetContents is the only one I'm aware of. Cheers, Simon

On Mon, November 6, 2006 9:21 am, Ross Paterson wrote:
On Mon, Nov 06, 2006 at 01:53:52PM +0000, Malcolm Wallace wrote:
So the doubly bizarre thing is that, actually, `seq` does not control the evaluation order (which is the only valid reason for wanting to use it in the first place), but nevertheless it undesirably changes the semantics of programs such that equational reasoning no longer holds.
When I've used seq, it's to ensure that a function is strict in that argument, and therefore has been evaluated before the function is called. (If the language had unlifted types, I might have used those instead). Beyond that, I don't care exactly when it was evaluated; it might be long before, thanks to propagation of strictness information.
seq has a clear denotational semantics. One can still do equational reasoning with it, though there will be side conditions about whether something is _|_ or not. The downside is that the eta rules get such side conditions, and polymorphic seq greatly weakens parametricity.
Apart from that, the only thing wrong with seq is its name.
What would be the correct way to get the effect that he expected from seq?
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
-- Seth Kurtzberg seth@cql.com Software Engineer Specializing in Reliability and Security

On Mon, Nov 06, 2006 at 05:21:04PM +0000, Ross Paterson wrote:
Apart from that, the only thing wrong with seq is its name.
I take back that part. Simon's "strong hint" suggestion looks like a good idea. It's just one of a number of implicit assumptions we make about operational behaviour. After all the Report doesn't actually say that monomorphic pattern-bound variables are shared, either.

On Mon, Nov 06, 2006 at 12:53:55PM +0000, Simon Marlow wrote:
Incedentally, this is also one reason I think lazy I/O is a wart (despite its obvious usefulness): because it necessarily requires talking about evaluation order.
What is lazy output? Buffering?

Ross Paterson wrote:
On Mon, Nov 06, 2006 at 12:53:55PM +0000, Simon Marlow wrote:
Incedentally, this is also one reason I think lazy I/O is a wart (despite its obvious usefulness): because it necessarily requires talking about evaluation order.
What is lazy output? Buffering?
Well ok, "lazy I" then :-) Cheers, Simon
participants (4)
-
Malcolm Wallace
-
Ross Paterson
-
Seth Kurtzberg
-
Simon Marlow