
Hi What is the role of $! ? As far as I can gather it's something to do with strict application. Could someone explain what it is meant by the term strict application please? Thanks, Paul

It's: f $! x = x `seq` f x That is, the argument to the right of $! is forced to evaluate, and then that value is passed to the function on the left. The function itself is not strictly evaluated (i.e., f x) I don't believe. Justin

On Nov 14, 2007 4:27 PM, Justin Bailey
It's:
f $! x = x `seq` f x
That is, the argument to the right of $! is forced to evaluate, and then that value is passed to the function on the left. The function itself is not strictly evaluated (i.e., f x) I don't believe.
Unless you mean f -- which I still don't think would do much -- it wouldn't make sense to evaluate (f x) strictly. (x `seq` x) is equivalent to (x), for any x (including (f x)). (Right?) Shachaf

On 14 Nov 2007, at 4:32 PM, Shachaf Ben-Kiki wrote:
On Nov 14, 2007 4:27 PM, Justin Bailey
wrote: It's:
f $! x = x `seq` f x
That is, the argument to the right of $! is forced to evaluate, and then that value is passed to the function on the left. The function itself is not strictly evaluated (i.e., f x) I don't believe.
Unless you mean f -- which I still don't think would do much -- it wouldn't make sense to evaluate (f x) strictly.
Right. (f x) evaluates f and then applies it to x. (f $! x) evaluates x, evaluates f, and then applies f to x. jcc

Jonathan Cast:
Right. (f x) evaluates f and then applies it to x. (f $! x) evaluates x, evaluates f, and then applies f to x.
True, though I'd like to chip in a small refinement: When evaluated, (f x) evaluates f as far as its top-level lambda, then applies it to x, and then continues to evaluate (only) to the extent demanded by its consumers. When evaluated, (f $! x) evaluates x to weak-head-normal-form (WHNF), and then evaluates (f x). I think the initial "when evaluated" is the most important part to remember when thinking about seq and lazy evaluation. It's the reason why (x `seq` x) is identical to x, as mentioned by someone else in this thread.

Hi okay, so $! is a bit like $ i.e. the equivalent of putting parentheses around the righthand expression. I'm still not sure of the difference between $ and $!. Maybe it's because I don't understand the meaning of "strict application". While we're on the subject, what's meant by Haskell being a non-strict language? Cheers Paul At 01:50 15/11/2007, you wrote:
On 14 Nov 2007, at 4:32 PM, Shachaf Ben-Kiki wrote:
On Nov 14, 2007 4:27 PM, Justin Bailey
wrote: It's:
f $! x = x `seq` f x
That is, the argument to the right of $! is forced to evaluate, and then that value is passed to the function on the left. The function itself is not strictly evaluated (i.e., f x) I don't believe.
Unless you mean f -- which I still don't think would do much -- it wouldn't make sense to evaluate (f x) strictly.
Right. (f x) evaluates f and then applies it to x. (f $! x) evaluates x, evaluates f, and then applies f to x.
jcc
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 17 Nov 2007, at 8:04 PM, PR Stanley wrote:
Hi okay, so $! is a bit like $ i.e. the equivalent of putting parentheses around the righthand expression. I'm still not sure of the difference between $ and $!. Maybe it's because I don't understand the meaning of "strict application". While we're on the subject, what's meant by Haskell being a non-strict language?
In most languages, if you have some expression E, and when the computer attempts to evaluate E it goes in to an infinite loop, then when the computer attempts to evaluate the expression f(E), it also goes into an infinite loop, regardless of what f is. That's the definition of a strict language. In Haskell, this isn't the case --- we can write functions f such that the computation f(E) terminates, even when E does not. (:) is one such function, as are some functions built from it, such as (++); xn ++ ys terminates whenever xn does, even if ys is an infinite loop. This is what makes it easy and convenient to build infinite loops in Haskell; in most strict languages, if you said let fibs = 0 : 1 : zipWith (+) fibs (tail fibs) the language would insist on evaluating fibs before it actually assigned anything to the memory cell for fibs, giving rise to an infinite loop. (For this reason, most strict languages make such definitions compile-time errors). Unfortunately, non-strictness turns out to be a pain in the ass to implement, since it means when the code generator sees an expression, it can't just generate code to evaluate it --- it has to hide the code somewhere else, and then substitute a pointer to that code for the value of the expression. There are a number of clever optimizations you can use here (indeed, most of the history of Haskell compilation techniques is a list of clever techniques to get around the limitations of compiling non-strict languages), but most of them rely on the compiler knowing that, in this case, if a sub- expression is an infinite loop, the entire expression is an infinite loop. This is actually pretty easy to figure out (most of the time), but sometimes the compiler needs a little help. That's where $! (usually) comes in. When the compiler sees (f $ x), it has to look at f to see whether, if x is an infinite loop, f $ x is one as well. When the compiler sees (f $! x), it doesn't need to look at f --- if x is an infinite loop, (f $! x) always is one as well. So, where in (f $ x) the compiler sometimes needs to put the code for x in a separate top-level block, to be called later when it's needed, in (f $! x) the compiler can always generate code for x inline, like a compiler for a normal language would. Since most CPU architectures are optimized for normal languages that compile f(E) by generating code for E inline, this is frequently a big speed-up. jcc

Hi Thanks for the response. JCC: In most languages, if you have some expression E, and when the computer attempts to evaluate E it goes in to an infinite loop, then when the computer attempts to evaluate the expression f(E), it also goes into an infinite loop, regardless of what f is. That's the definition of a strict language. PRS: Does that mean that a strict language is also imperative? Either e or f(e) could result in an infinite loop. JCC: In Haskell, this isn't the case ---we can write functions f such that the computation f(E) terminates, even when E does not. (:) is one such function, as are some functions built from it, such as (++); xn ++ ys terminates whenever xn does, even if ys is an infinite loop. This is what makes it easy and convenient to build infinite loops in Haskell; in most strict languages, if you said let fibs = 0 : 1 : zipWith (+) fibs (tail fibs) the language would insist on evaluating fibs before it actually assigned anything to the memory cell for fibs, giving rise to an infinite loop. (For this reason, most strict languages make such definitions compile-time errors). Unfortunately, non-strictness turns out to be a pain in the ass to implement, since it means when the code generator sees an expression, it can't just generate code to evaluate it --- it has to hide the code somewhere else, and then substitute a pointer to that code for the value of the expression. PRS: Is there a kind of strictness applied when the compiler/interpreter sorts the various sub-expressions into little memory compartments indexed with pointers for later evaluation? To put it another way, does lazy evaluation begin with the outer-most expression, the most abstract, and determine what sshould go where in relation to the subsequent inner expressions? For example: takeWhile (<20) [0..9] ++ [10..] The compiler determiens at the outset that the result of takeWhile is a list followed by the calculation of the length of that list based on the predicate (<20), and then calls ++ which is for all intents and purposes on its own an infinite loop. Is this what happens? This is a very simple example, that's to say, I am aware that the compiler may be faced with a much more complex job of applying lazy evaluation. Nevertheless, I wonder if there are a set of fundamental rules to which the compiler must always adhere in lazy evaluation. JCC: There are a number of clever optimizations you can use here (indeed, most of the history of Haskell compilation techniques is a list of clever techniques to get around the limitations of compiling non-strict languages), but most of them rely on the compiler knowing that, in this case, if a sub- expression is an infinite loop, the entire expression is an infinite loop. This is actually pretty easy to figure out (most of the time), but sometimes the compiler needs a little help. That's where $! (usually) comes in. When the compiler sees (f $ x), it has to look at f to see whether, if x is an infinite loop, f $ x is one as well. When the compiler sees (f $! x), it doesn't need to look at f --- if x is an infinite loop, (f $! x) always is one as well. So, where in (f $ x) the compiler sometimes needs to put the code for x in a separate top-level block, to be called later when it's needed, in (f $! x) the compiler can always generate code for x inline, like a compiler for a normal language would. Since most CPU architectures are optimized for normal languages that compile f(E) by generating code for E inline, this is frequently a big speed-up. PrS: Your description of $! reminds me of the difference between inline functions and "ordinary" functions in C++ with the former being faster. Am I on the right track? In either case, (f $ x) and (f $! x), lazy evaluation must be applied at a higher level otherwise either instruction could result in an infinite loop. Therefore, is efficiency the only consideration here? If Haskell is a lazy language and $ merely implies lazy evaluation then what's the difference between (f $ x \oplus y) and (f (x \oplus y))? Thanks, Paul

On 29 Nov 2007, at 06:32, PR Stanley wrote:
Hi Thanks for the response.
JCC: In most languages, if you have some expression E, and when the computer attempts to evaluate E it goes in to an infinite loop, then when the computer attempts to evaluate the expression f(E), it also goes into an infinite loop, regardless of what f is. That's the definition of a strict language.
PRS: Does that mean that a strict language is also imperative?
Nope, not at all. Just a strict language has slightly fewer programs it can evaluate correctly, as more will loop infinitely.
Either e or f(e) could result in an infinite loop.
JCC: In Haskell, this isn't the case ---we can write functions f such that the computation f(E) terminates, even when E does not. (:) is one such function, as are some functions built from it, such as (++); xn ++ ys terminates whenever xn does, even if ys is an infinite loop. This is what makes it easy and convenient to build infinite loops in Haskell; in most strict languages, if you said let fibs = 0 : 1 : zipWith (+) fibs (tail fibs) the language would insist on evaluating fibs before it actually assigned anything to the memory cell for fibs, giving rise to an infinite loop. (For this reason, most strict languages make such definitions compile-time errors).
Unfortunately, non-strictness turns out to be a pain in the ass to implement, since it means when the code generator sees an expression, it can't just generate code to evaluate it --- it has to hide the code somewhere else, and then substitute a pointer to that code for the value of the expression.
PRS: Is there a kind of strictness applied when the compiler/ interpreter sorts the various sub-expressions into little memory compartments indexed with pointers for later evaluation? To put it another way, does lazy evaluation begin with the outer-most expression, the most abstract, and determine what sshould go where in relation to the subsequent inner expressions? For example:
takeWhile (<20) [0..9] ++ [10..]
The compiler determiens at the outset that the result of takeWhile is a list followed by the calculation of the length of that list based on the predicate (<20), and then calls ++ which is for all intents and purposes on its own an infinite loop. Is this what happens?
Not really. For lazy evaluation the compiler doesn't "decide" the order statically -- it merely gives the program rules to follow for what the next expression to be evaluated should be. Lets look at a slightly simpler example: takeWhile (< 2) (map (+1) [0..]) We will always attempt to evaluate the outermost left most expression. We do this by matching against the rules given in the program, to make this clearer, here are the rules for takeWhile and map: takeWhile _ [] = [] takeWhile p (x:xs) | p x = x : takeWhile p xs | otherwise = [] map _ [] = [] map f (x:xs) = f x : map f xs takeWhile (< 2) (map (+1) [0..]) -- We start by evaluating the leftmost outermost expression. We attempt to match on the first rule of takeWhile, and discover that we can't because we don't know whether the result of (map (+1) [0..]) is the empty list or not. Therefore we demand the evaluation of (map +1) [0..]) -> takeWhile (< 2) ((+1) 0 : map (+1) [1..]) -- We now know that we don't have the empty list, so we must use the second rule of takeWhile. We must evaluate the guard first though: -> (<2) ((+1) 0) | -- To do this, we must evaluate ((+1) 0) -> (<2) 1 | -- This evaluates to True, so we may insert the right hand side -- note that x remains evaluated -> True | 1 : takeWhile (<2) (map (+1) [1..]) -- We can drop the guard now, but lets carry on. We have already evaluated the outermost expression, so lets evaluate the next in. Again pattern matching on takeWhile demands the evaluation of map: -> 1 : takeWhile (<2) ((+1) 1 : map (+1) [2..]) -- We again, can pattern match on takeWhile, and must evaluate the guard again: -> 1 : ((<2) ((+1) 1) |) -- Again, we must evaluate the result of the addition -> 1 : ((<2) 2 |) -- This time we get False, so we must evaluate the next guard -> 1 : (otherwise |) -- otherwise is a synonym for True, so we use this right hand side. -> 1 : (True | []) -- and we can get rid of the guard, and prettify the result, giving us: -> [1] Note that we followed a set of rules that gave us non-strict semantics. The set of rules is called lazy evaluation. We may come up with several other sets of rules that give us different evaluation orders, but still non-strict semantics (e.g. Optimistic Evaluation).
This is a very simple example, that's to say, I am aware that the compiler may be faced with a much more complex job of applying lazy evaluation. Nevertheless, I wonder if there are a set of fundamental rules to which the compiler must always adhere in lazy evaluation.
JCC: There are a number of clever optimizations you can use here (indeed, most of the history of Haskell compilation techniques is a list of clever techniques to get around the limitations of compiling non-strict languages), but most of them rely on the compiler knowing that, in this case, if a sub- expression is an infinite loop, the entire expression is an infinite loop. This is actually pretty easy to figure out (most of the time), but sometimes the compiler needs a little help.
That's where $! (usually) comes in. When the compiler sees (f $ x), it has to look at f to see whether, if x is an infinite loop, f $ x is one as well. When the compiler sees (f $! x), it doesn't need to look at f --- if x is an infinite loop, (f $! x) always is one as well. So, where in (f $ x) the compiler sometimes needs to put the code for x in a separate top-level block, to be called later when it's needed, in (f $! x) the compiler can always generate code for x inline, like a compiler for a normal language would. Since most CPU architectures are optimized for normal languages that compile f(E) by generating code for E inline, this is frequently a big speed-up.
PrS: Your description of $! reminds me of the difference between inline functions and "ordinary" functions in C++ with the former being faster. Am I on the right track? In either case, (f $ x) and (f $! x), lazy evaluation must be applied at a higher level otherwise either instruction could result in an infinite loop. Therefore, is efficiency the only consideration here?
If Haskell is a lazy language and $ merely implies lazy evaluation then what's the difference between (f $ x \oplus y) and (f (x \oplus y))?
$ does not mean "do lazy evaluation" it means "apply". It's a function, like any other: f ($) x = f x All it does is takes the function, and the argument and applies one to the other, it can be used for eliminating ugly bracketing, or is useful in creating sections, e.g.
map ($ 5) [(1 +), (2 *), (3 ^)] [6, 10, 243]
$! is the special case, which means strictly apply. It evaluates its argument first, *then* does the application. This may or may not be faster (and usually isn't, due to evaluating more of the argument): f ($!) x = seq x (f x) seq is a special function that says "first fully evaluate my first argument, then return my second argument", it breaks non-strict semantics. Personally, my only use for such functions is a little bit of debugging work, seq for example can be used to force something to be printed whenever an expression is evaluated: seq (unsafePerformIO $ putStrLn "At the nasty evaluation") (some problematic expression) There is however a nicer version of this in the libraries, that masks it nicely for me: trace "At the nasty evaluation" (some problematic expression) I hope this helped somewhat. Tom Davie

On Thu, 2007-11-29 at 07:29 +0000, Thomas Davie wrote:
On 29 Nov 2007, at 06:32, PR Stanley wrote:
Hi Thanks for the response.
JCC: In most languages, if you have some expression E, and when the computer attempts to evaluate E it goes in to an infinite loop, then when the computer attempts to evaluate the expression f(E), it also goes into an infinite loop, regardless of what f is. That's the definition of a strict language.
PRS: Does that mean that a strict language is also imperative?
Nope, not at all. Just a strict language has slightly fewer programs it can evaluate correctly, as more will loop infinitely.
A -pure- strict language.
$ does not mean "do lazy evaluation" it means "apply". It's a function, like any other:
f ($) x = f x
The syntax for defining an infix operator is: f $ x = f x -- or ($) f x = f x The latter form more clearly illustrates something that drives home the fact that ($) is completely trivial, namely, a third definition for ($) is: ($) = id
$! is the special case, which means strictly apply. It evaluates its argument first, *then* does the application. This may or may not be faster (and usually isn't, due to evaluating more of the argument):
f ($!) x = seq x (f x)
Again, f $! x = seq x (f x) -- or x `seq` f x This is the definition according to the Report.
seq is a special function that says "first fully evaluate my first argument, then return my second argument", it breaks non-strict semantics. Personally, my only use for such functions is a little bit of debugging work [...]
seq, or something that forces evaluation, is more important than that (though I wouldn't mind it being put back in a class.) E.g. (assuming no strictness analysis which can't be relied upon to -always- work), both sum = foldr (+) 0 and sum = foldl (+) 0 will stack overflow on a large enough input list, while sum = foldl' (+) 0 will not. The difference between foldl and foldl' is that, via seq, foldl' is a bit more strict.

Thanks, Tom, for a nice description of lazy evaluation. Besides the minor things Derek pointed out, there's one more subtle but important thing to correct: At 7:29 AM +0000 11/29/07, Thomas Davie wrote:
$! is the special case, which means strictly apply. It evaluates its argument first, *then* does the application. This may or may not be faster (and usually isn't, due to evaluating more of the argument):
f ($!) x = seq x (f x)
seq is a special function that says "first fully evaluate my first argument, then return my second argument", it breaks non-strict semantics.
seq doesn't fully evaluate its first argument, rather only to what's called "weak head normal form". Roughly, that means only enough to establish the top-level constructor (e.g., to distinguish [] from (_:_)). Dean

PR Stanley wrote:
Hi okay, so $! is a bit like $ i.e. the equivalent of putting parentheses around the righthand expression. I'm still not sure of the difference between $ and $!. Maybe it's because I don't understand the meaning of "strict application". While we're on the subject, what's meant by Haskell being a non-strict language? Cheers Paul
It simply means in Haskell, if you call a function, that function is not executed until you try to do something with the result. "f $ x + y" is like "f (x + y)". The value of "x + y" will only actually be calculated if "f" tries to examine its value. For example, f1 x = 7 f2 x = if x == 0 then 0 else 1 The "f1" function ignores "x" and always returns "7". If you did "f1 $ x + y", then "x + y" would never ever be calculated at all. However, "f2" looks at "x" to see if it's 0. So if you do "f2 $ x + y", the "x + y" part will be calculated. "f $! x + y" is just like "f $ x + y", except that "x + y" will be calculated *before* "f" is called - regardless of whether "f" does anything with this data. The usual reason for doing this is to avoid large unevaluated expressions accumulating inside a program loop - e.g., if you were calculating a total, you probably want the "total" variable to actually contain the total rather than just a big expression like "1 + 2 + 3 + ...", so you could use $! to force the total to actually be calculated before starting the next loop [which will be a recursive function call]. Make any sense? PS. There is a technical distinction between the terms "lazy" and "non-strict", and also the opposite terms "eger" and "strict". I couldn't tell you what that is.

Andrew Coppin wrote:
PS. There is a technical distinction between the terms "lazy" and "non-strict", and also the opposite terms "eger" and "strict". I couldn't tell you what that is.
As I understand it, the distinction is between the mathematical term "non-strict" and the implementation method of "lazy". "Non-strict" means that "reduction" (the mathematical term for evaluation) proceeds from the outside in, so if I have (a+(b*c)) then first you reduce the "+", then you reduce the inner (b*c). Strict languages work the other way around, starting with the innermost brackets and working outwards. This matters to the semantics because if you have an expression that evaluates to "bottom" (i.e. an error, exception or endless loop) then any language that starts at the inside and works outwards will always find that bottom value, and hence the bottom will propogate outwards. However if you start from the outside and work in then some of the sub-expressions are eliminated by the outer reductions, so they don't get evaluated and you don't get "bottom". Lazy evaluation, on the other hand, means only evaluating an expression when its results are needed (note the shift from "reduction" to "evaluation"). So when the evaluation engine sees an expression it builds a "thunk" data structure containing whatever values are needed to evaluate the expression, plus a pointer to the expression itself. When the result is actually needed the evaluation engine calls the expression and then replaces the thunk with the result for future reference. Obviously there is a strong correspondance between a thunk and a partly-evaluated expression. Hence in most cases the terms "lazy" and "non-strict" are synonyms. But not quite. For instance you could imagine an evaluation engine on highly parallel hardware that fires off sub-expression evaluation eagerly, but then throws away results that are not needed. In practice Haskell is not a purely lazy language: for instance pattern matching is usually strict (so trying a pattern match forces evaluation to happen at least far enough to accept or reject the match). The optimiser also looks for cases where sub-expressions are *always* required by the outer expression, and converts those into eager evaluation. It can do this because the semantics (in terms of "bottom") don't change. Programmers can also use the "seq" primitive to force an expression to evaluate regardless of whether the result will ever be used. "$!" is defined in terms of "seq". Paul.

On Nov 18, 2007 9:23 AM, Paul Johnson
Obviously there is a strong correspondance between a thunk and a partly-evaluated expression. Hence in most cases the terms "lazy" and "non-strict" are synonyms. But not quite. For instance you could imagine an evaluation engine on highly parallel hardware that fires off sub-expression evaluation eagerly, but then throws away results that are not needed.
I've mostly seen "lazy evaluation" used for the strategy where thunks
are only evaluated once.
Consider the function "f x = g x x" and the code "f (a + b)". Because
Haskell is lazy, it only evaluates "a + b" once, even though "f (a +
b)" reduces to "g (a + b) (a + b)".
In Haskell, the only difference between "f (a + b)" and "g (a + b) (a
+ b)" is efficiency, but there are languages that have non-strict
functions and side-effects. In Algol, IIRC, you could define function
parameters to be call-by-name. A function call like "f(inc(y))" would
not evaluate "inc(y)" until f used its parameter, but it would
evaluate it again each time.
The difference between call-by-name and laziness (aka call-by-need) is
analogous to the difference between these monadic functions:
f1 m = m >>= \x -> g x x
f2 m = m >>= \x1 -> m >>= \x2 -> g x1 x2
--
Dave Menendez

Paul Johnson wrote:
Andrew Coppin wrote:
PS. There is a technical distinction between the terms "lazy" and "non-strict", and also the opposite terms "eger" and "strict". I couldn't tell you what that is.
As I understand it, the distinction is between the mathematical term "non-strict" and the implementation method of "lazy". "Non-strict" means that "reduction" (the mathematical term for evaluation) proceeds from the outside in, so if I have (a+(b*c)) then first you reduce the "+", then you reduce the inner (b*c). Strict languages work the other way around, starting with the innermost brackets and working outwards. [...]
Almost right, but strict and non-strict aren't tied to an operational semantics. In other words, you can talk about _|_ and strictness without knowing how to evaluate your expressions at all. See also http://en.wikibooks.org/wiki/Haskell/Denotational_semantics . For more on the details of lazy evaluation (which actually does work "outside in"), there's the incomplete http://en.wikibooks.org/wiki/Haskell/Graph_reduction . Of course, strict and eager as well as non-strict and lazy have pretty much the same effect and can be used synonymously, but they're different things nonetheless. Regards, apfelmus

Hi Thanks for the explanation. I would be grateful for some examples accompanying the text. I will indicate the right places for real life (Haskell code) examples in the paragraphs below: PJ: As I understand it, the distinction is between the mathematical term "non-strict" and the implementation method of "lazy". Non-strict" means that "reduction" (the mathematical term for evaluation) proceeds from the outside in, so if I have (a+(b*c)) then first you reduce the "+", then you reduce the inner (b*c). PRS: No problems so far.. PJ: Strict languages work the other way around, starting with the innermost brackets and working outwards. This matters to the semantics because if you have an expression that evaluates to "bottom" (i.e. an error, exception or endless loop) then any language that starts at the inside and works outwards will always find that bottom value, and hence the bottom will propogate outwards. PRS: You would also get different results - e.g. let a = 3, b = 7, c = 2 therefore 20 = strict ( ( (a+(b*c)) ) therefore 17 = non-strict ( (a+(b*c)) ) or am I misunderstanding the concept? PJ: However if you start from the outside and work in then some of the sub-expressions are eliminated by the outer reductions, so they don't get evaluated and you don't get "bottom". PRS: I'm not sure if I fully understand the bottom idea here. I thought it related to the base value in a recursive pattern. For example: f (.) [] = [] f . (x:xs) = x . f xs What's a sub-expression? PJ: Lazy evaluation, on the other hand, means only evaluating an expression when its results are needed (note the shift from "reduction" to "evaluation"). So when the evaluation engine sees an expression it builds a "thunk" data structure containing whatever values are needed to evaluate the expression, plus a pointer to the expression itself. When the result is actually needed the evaluation engine calls the expression and then replaces the thunk with the result for future reference. PRS: A thunk data structure? Again, a example would be nice. PJ: Obviously there is a strong correspondance between a thunk and a partly-evaluated expression. Hence in most cases the terms "lazy" and "non-strict" are synonyms. But not quite. For instance you could imagine an evaluation engine on highly parallel hardware that fires off sub-expression evaluation eagerly, but then throws away results that are not needed. In practice Haskell is not a purely lazy language: for instance pattern matching is usually strict (so trying a pattern match forces evaluation to happen at least far enough to accept or reject the match). The optimiser also looks for cases where sub-expressions are *always* required by the outer expression, and converts those into eager evaluation. It can do this because the semantics (in terms of "bottom") don't change. Programmers can also use the "seq" primitive to force an expression to evaluate regardless of whether the result will ever be used. "$!" is defined in terms of "seq". PRS: More examples please. Thanks, Paul

On Nov 29, 2007 4:23 AM, PR Stanley
PRS: You would also get different results - e.g. let a = 3, b = 7, c = 2 therefore 20 = strict ( ( (a+(b*c)) ) therefore 17 = non-strict ( (a+(b*c)) )
or am I misunderstanding the concept?
Yes. If the strict program does not error, then the strict program and the lazy program will have the same results. Numerics are not the best way to illustrate the difference, because they are essentially strict in their semantics. How about a list function: head [] = error "empty list" head (x:xs) = x map f [] = [] map f (x:xs) = f x:map f xs head (map (+1) [1,2,3]) -- rewrite as... head (map (+1) (1:2:3:[])) Strictly would go like this: head (map (+1) (1:2:3:[])) -- evaluate map (+1) (1:2:3:[]) head ((1+1) : map (+1) (2:3:[])) -- evaluate 1+1 head (2 : map (+1) (2:3:[])) -- evaluate map (+1) (2:3:[]) head (2 : (2+1) : map (+1) (3:[])) -- evaluate 2+1 head (2 : 3 : map (+1) (3:[])) -- evaluate map (+1) (3:[]) head (2 : 3 : (3+1) : []) -- evaluate 3+1 head (2 : 3 : 4 : []) -- evaluate [] (nothing to do) head (2 : 3 : 4 : []) -- evaluate head 2 Lazily would go like this: head (map (+1) (1:2:3:[])) -- evaluate head -- try to match map (+1) (1:2:3:[]) -- against x:xs, need to evaluate map head ((1+1) : map (+1) (2:3:[])) -- evaluate head -- match (1+1):map (+1) (2:3:[]) against -- x:xs succeeds, with x = (1+1) (1+1) -- evaluate (1+1) 2 Here I'm describing lazy evaluation rather than non-strict semantics, but they're pretty closely related. Luke

Here is a practical example I ran into a few days ago. With this
expression:
writeFile path (compute text)
the file at path would be overwritten with an empty file if an error occurs
while evaluating (compute text). With this one:
writeFile path $! (compute text)
the file alone when an error occurs.
On Nov 17, 2007 8:04 PM, PR Stanley
Hi okay, so $! is a bit like $ i.e. the equivalent of putting parentheses around the righthand expression. I'm still not sure of the difference between $ and $!. Maybe it's because I don't understand the meaning of "strict application". While we're on the subject, what's meant by Haskell being a non-strict language? Cheers Paul At 01:50 15/11/2007, you wrote:
On 14 Nov 2007, at 4:32 PM, Shachaf Ben-Kiki wrote:
On Nov 14, 2007 4:27 PM, Justin Bailey
wrote: It's:
f $! x = x `seq` f x
That is, the argument to the right of $! is forced to evaluate, and then that value is passed to the function on the left. The function itself is not strictly evaluated (i.e., f x) I don't believe.
Unless you mean f -- which I still don't think would do much -- it wouldn't make sense to evaluate (f x) strictly.
Right. (f x) evaluates f and then applies it to x. (f $! x) evaluates x, evaluates f, and then applies f to x.
jcc
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Argh, that last sentence should read "the file is left alone"..
On Dec 9, 2007 10:15 PM, David Fox
Here is a practical example I ran into a few days ago. With this expression:
writeFile path (compute text)
the file at path would be overwritten with an empty file if an error occurs while evaluating (compute text). With this one:
writeFile path $! (compute text)
the file alone when an error occurs.
On Nov 17, 2007 8:04 PM, PR Stanley
wrote: Hi okay, so $! is a bit like $ i.e. the equivalent of putting parentheses around the righthand expression. I'm still not sure of the difference between $ and $!. Maybe it's because I don't understand the meaning of "strict application". While we're on the subject, what's meant by Haskell being a non-strict language? Cheers Paul At 01:50 15/11/2007, you wrote:
On 14 Nov 2007, at 4:32 PM, Shachaf Ben-Kiki wrote:
On Nov 14, 2007 4:27 PM, Justin Bailey < jgbailey@gmail.com> wrote:
It's:
f $! x = x `seq` f x
That is, the argument to the right of $! is forced to evaluate, and then that value is passed to the function on the left. The function itself is not strictly evaluated (i.e., f x) I don't believe.
Unless you mean f -- which I still don't think would do much -- it wouldn't make sense to evaluate (f x) strictly.
Right. (f x) evaluates f and then applies it to x. (f $! x) evaluates x, evaluates f, and then applies f to x.
jcc
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

David Fox wrote:
Here is a practical example I ran into a few days ago. With this expression:
writeFile path (compute text)
the file at path would be overwritten with an empty file if an error occurs while evaluating (compute text). With this one:
writeFile path $! (compute text)
the file alone when an error occurs.
If I understand you correctly, that would be because compute text is capable of throwing an exception. That, then, is the danger of using exceptions in pure code. Personally I'd use an error-signalling type (like Either) and then this wouldn't be an issue. Jules

On Wed, 2007-11-14 at 16:27 -0800, Justin Bailey wrote:
It's:
f $! x = x `seq` f x
That is, the argument to the right of $! is forced to evaluate, and then that value is passed to the function on the left. The function itself is not strictly evaluated (i.e., f x) I don't believe.
Application is strict so f is forced and id is strict so f x is forced.

Please note that if you're using GHC, bang patterns are often much more convenient than $! or seq when you want to enforce strictness: http://www.haskell.org/ghc/docs/latest/html/users_guide/bang-patterns.html Lauri

Lauri Alanko wrote:
Please note that if you're using GHC, bang patterns are often much more convenient than $! or seq when you want to enforce strictness:
http://www.haskell.org/ghc/docs/latest/html/users_guide/bang-patterns.html
Wait, so... f x = x + 1; f $! (a + b) and f !x = x + 1; f (a + b) mean the same thing? Well, you learn something new every day... (I guess wanting a function's arguments to evaluate before the rest of that function is quite a common thing to want. Neat!)

Hello Andrew, Sunday, November 18, 2007, 10:04:15 PM, you wrote:
Wait, so...
f x = ... g = f $! x
and
f !x = ... g = f x
mean the same thing?
in both cases, x is evaluated before evaluating body of x. but of course, this happens only at the moment when value of (f x) itself is required -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Sun, 18 Nov 2007, Andrew Coppin wrote:
Lauri Alanko wrote:
Please note that if you're using GHC, bang patterns are often much more convenient than $! or seq when you want to enforce strictness:
http://www.haskell.org/ghc/docs/latest/html/users_guide/bang-patterns.html
Wait, so...
f x = x + 1; f $! (a + b)
and
f !x = x + 1; f (a + b)
mean the same thing?
Well, you learn something new every day... (I guess wanting a function's arguments to evaluate before the rest of that function is quite a common thing to want. Neat!)
For my taste it makes the language more complicated that sometimes 'lazy' is default and 'strict' must be enforced and in other cases it is the other way round. Would it be a good idea to make 'lazy' the default and 'strict' optional, and the strictness analyzer handles the obvious cases where there is no difference?

rather than ask the role of $! I found it helpful to first grasp the role
of seq, since $! is defined in terms of seq and seq is a "primitive"
operation (no prelude definition, like with IO, it's a "given").
What helped me grasp seq was its role in a strict fold.
Basically, try to sum all the numbers from 1 to a million. Prelude "sum"
probably gives stack overflow (if not, up it to a billion ;) ), and so
will a naive fold, as is explained at
http://www.haskell.org/haskellwiki/Stack_overflow
The code below basically restates what was already on the wiki, but I
found my definitions of foldl' (using seq, bang patterns, and $!) easier
to understand than the definition on the wiki page, and the definition
from Data.List. (Maybe I'll edit the wiki.)
t.
{-# LANGUAGE BangPatterns #-}
-- stack overflow
t1 = myfoldl (+) 0 [1..10^6]
-- works, as do myfoldl'' and myfoldl'''
t2 = myfoldl' (+) 0 [1..10^6]
-- (myfoldl f q ) is a curried function that takes a list
-- If I understand currectly, in this "lazy" fold, this curried function
isn't applied immediately, because
-- by default the value of q is still a thunk
myfoldl f z [] = z
myfoldl f z (x:xs) = ( myfoldl f q ) xs
where q = z `f` x
-- here, because of the definition of seq, the curried function (myfoldl'
f q) is applied immediately
-- because the value of q is known already, so (myfoldl' f q ) is WHNF
myfoldl' f z [] = z
myfoldl' f z (x:xs) = seq q ( myfoldl' f q ) xs
where q = z `f` x
--same as myfoldl'
myfoldl'' f z [] = z
myfoldl'' f !z (x:xs) = ( myfoldl'' f q ) xs
where q = z `f` x
myfoldl''' f z [] = z
myfoldl''' f z (x:xs) = (myfoldl''' f $! q) xs
where q = z `f` x
PR Stanley

Thomas Hartman wrote:
-- (myfoldl f q ) is a curried function that takes a list -- If I understand currectly, in this "lazy" fold, this curried function isn't applied immediately, because -- by default the value of q is still a thunk myfoldl f z [] = z myfoldl f z (x:xs) = ( myfoldl f q ) xs where q = z `f` x
Sorry to say "this curried function isn't applied immediately" is wrong. The curried function is applied immediately. This is independent of what happens to q. q remains a thunk. myfoldl f q xs moves on immediately. Next iteration's z is this iteration's q, and remains a thunk too. It is also noteworthy that a b c d = (a b c) d = ((a b) c) d They are syntactic sugar of each other.
-- here, because of the definition of seq, the curried function (myfoldl' f q) is applied immediately -- because the value of q is known already, so (myfoldl' f q ) is WHNF myfoldl' f z [] = z myfoldl' f z (x:xs) = seq q ( myfoldl' f q ) xs where q = z `f` x
The seq causes q to become WHNF. This is independent of what happens to (myfoldl' f q). In general in many compilers seq x y digresses to reduce x to WHNF, then "we now return you to the scheduled programming of whatever should happen to y".
--same as myfoldl' myfoldl'' f z [] = z myfoldl'' f !z (x:xs) = ( myfoldl'' f q ) xs where q = z `f` x
This is not the same as myfoldl'. This does not reduce q to WHNF - not now. Instead, z is reduced to WHNF now. As for q, this iteration's q becomes the next iteration's z, so this iteration's q will become WHNF next iteration. It is unusual to observe any difference because usually one experiments with number crunching only, where no one cares whether evaluation is one iteration early or late. However, this operator will show the difference. mydisj _ True = True mydisj True False = True mydisj False False = False myfoldl' mydisj (error "bottom") [True] --> True myfoldl'' mydisj (error "bottom") [True] --> exception: bottom
myfoldl''' f z [] = z myfoldl''' f z (x:xs) = (myfoldl''' f $! q) xs where q = z `f` x
This is the same as myfold'. myfold' and myfold''' are the same as what's on the wiki.
participants (20)
-
Albert Y. C. Lai
-
Andrew Coppin
-
apfelmus
-
Bulat Ziganshin
-
David Fox
-
David Menendez
-
Dean Herington
-
Derek Elkins
-
Henning Thielemann
-
Jonathan Cast
-
Jules Bean
-
Justin Bailey
-
Lauri Alanko
-
Luke Palmer
-
Matthew Brecknell
-
Paul Johnson
-
PR Stanley
-
Shachaf Ben-Kiki
-
Thomas Davie
-
Thomas Hartman