
On 19 March 2006 02:35, Manuel M T Chakravarty wrote:
Loosely related to Ticket #76 (Bang Patterns) is the question of whether we want the language to include strict tuples. It is related to bang patterns, because its sole motivation is to simplify enforcing strictness for some computations. Its about empowering the programmer to choose between laziness and strictness where they deem that necessary without forcing them to completely re-arrange sub-expressions (as seq does).
So what are strict tupples? If a lazy pair is defined in pseudo code as
data (a, b) = (a, b)
a strict pair would be defined as
data (!a, b!) = ( !a, !b )
Ie, a strict tuple is enclosed by bang parenthesis (! ... !). The use of the ! on the rhs are just the already standard strict data type fields.
Why strict tuples, but not strict lists and strict Maybe and so on? Tuples are the Haskell choice of returning more than one result from a function. So, if I write
add x y = x + y
the caller gets an evaluated result. However, if I write
addmul x y = (x + y, x * y)
the caller gets a pair of two unevaluated results. Even with bang patterns, I still have to write
addmul x y = let !s = x + y; !p = x * y in (s, p)
to have both results evaluated. With strict tuples
addmul x y = (!x + y, x * y!)
suffices.
Of course, the caller could invoke addmul using a bang patterns, as in
let ( !s, !p ) = addmul x y in ...
but that's quite different to statically knowing (from the type) that the two results of addmul will already be evaluated. The latter leaves room for more optimisations.
Syntax issues ~~~~~~~~~~~~~ * In Haskell (,) is the pair constructor. What should be use for strict tuples? (!,!) ? * With strict tuples (! and !) would become some sort of reserved/special symbol. That interferes with bang patterns, as (!x, y!) would be tokenized as (! x , y !). We could use ( ... !) for strict tuples to avoid that conflict, or just requires that the user write ( !x, !y ) when they want a bang pattern. (Just like you cannot write `Just.x' to mean `Just . x' as the former will always be read as a qualified name and not the application of function composition.
Not to mention overlap with sections: (!i). Even with just bang patterns, we have some interesting parsing problems due to the overlap with infix '!'. eg., now arr ! x = indexArray arr x will probably parse as arr (!x) = indexArray arr x which means that in order to define (!) you have to use the prefix form: (!) arr x = ... GHC's implementation of bang pattern parsing has some ugliness to deal with this. In the report, we will have to be very careful to make sure the syntax doesn't have any ambiguities in this area, which will probably mean adding special cases to the grammar. My suggestion is to avoid these problems by removing infix '!' from the syntax: http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/ArrayIndex ing I realise this is a code-breaking change, but I consider the special cases introduced to the syntax by bang patterns to be rather warty. Also, since I think many of us envisage Haskell moving towards having more strictness annotations in the future, it makes sense to consistently use the '!' operator to mean "strict". Cheers, Simon

Simon Marlow:
Not to mention overlap with sections: (!i). Even with just bang patterns, we have some interesting parsing problems due to the overlap with infix '!'. eg., now
arr ! x = indexArray arr x
will probably parse as
arr (!x) = indexArray arr x
which means that in order to define (!) you have to use the prefix form: (!) arr x = ...
GHC's implementation of bang pattern parsing has some ugliness to deal with this. In the report, we will have to be very careful to make sure the syntax doesn't have any ambiguities in this area, which will probably mean adding special cases to the grammar.
My suggestion is to avoid these problems by removing infix '!' from the syntax:
http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/ArrayIndex ing
I realise this is a code-breaking change, but I consider the special cases introduced to the syntax by bang patterns to be rather warty. Also, since I think many of us envisage Haskell moving towards having more strictness annotations in the future, it makes sense to consistently use the '!' operator to mean "strict".
I agree that the use of ! for indexing is a bad choice, actually a very bad choice. As arrays are not used that much and (!) isn't even exported from the Prelude, I like the idea of changing the indexing syntax. I am less convinced that it is wise to change the syntax of function composition, as this will break a huge set of programs. I actually also don't see that this affects the array proposal. (.#) would be a valid and free operator anyway, wouldn't it? What about list indexing? Use (.##)? (Doesn't look very nice, but transfers the (!) for arrays and (!!) for lists idea.) A change to list indexing will probably break more programs than a change to array indexing. Apart from the syntactic issues, does anybody else support the idea of strict tuples as proposed? I just want to know whether I am alone on this before putting it on the wiki. Manuel
On 19 March 2006 02:35, Manuel M T Chakravarty wrote:
Loosely related to Ticket #76 (Bang Patterns) is the question of whether we want the language to include strict tuples. It is related to bang patterns, because its sole motivation is to simplify enforcing strictness for some computations. Its about empowering the programmer to choose between laziness and strictness where they deem that necessary without forcing them to completely re-arrange sub-expressions (as seq does).
So what are strict tupples? If a lazy pair is defined in pseudo code as
data (a, b) = (a, b)
a strict pair would be defined as
data (!a, b!) = ( !a, !b )
Ie, a strict tuple is enclosed by bang parenthesis (! ... !). The use of the ! on the rhs are just the already standard strict data type fields.
Why strict tuples, but not strict lists and strict Maybe and so on? Tuples are the Haskell choice of returning more than one result from a function. So, if I write
add x y = x + y
the caller gets an evaluated result. However, if I write
addmul x y = (x + y, x * y)
the caller gets a pair of two unevaluated results. Even with bang patterns, I still have to write
addmul x y = let !s = x + y; !p = x * y in (s, p)
to have both results evaluated. With strict tuples
addmul x y = (!x + y, x * y!)
suffices.
Of course, the caller could invoke addmul using a bang patterns, as in
let ( !s, !p ) = addmul x y in ...
but that's quite different to statically knowing (from the type) that the two results of addmul will already be evaluated. The latter leaves room for more optimisations.
Syntax issues ~~~~~~~~~~~~~ * In Haskell (,) is the pair constructor. What should be use for strict tuples? (!,!) ? * With strict tuples (! and !) would become some sort of reserved/special symbol. That interferes with bang patterns, as (!x, y!) would be tokenized as (! x , y !). We could use ( ... !) for strict tuples to avoid that conflict, or just requires that the user write ( !x, !y ) when they want a bang pattern. (Just like you cannot write `Just.x' to mean `Just . x' as the former will always be read as a qualified name and not the application of function composition.

On Mon, Mar 20, 2006 at 09:39:41AM -0500, Manuel M T Chakravarty wrote:
Apart from the syntactic issues, does anybody else support the idea of strict tuples as proposed? I just want to know whether I am alone on this before putting it on the wiki.
I have a few issues though, not entirely easy to articulate. I worry about all the (! .. !) types that will appear in interfaces, making things like (map fst) not work. It has been my experience that a lot of things that should be strict that are obvious to the user, are often obvious to the compiler as well. having the user place redundant strictness annotations in can ofsucate where the actual performance fixes are. As in, are lazy tuples actually a source of problems or are we just guessing? ghc's strictness analyzer is pretty darn good, If something is subtle enough for the compiler not to catch it, then the programmer probably won't right off the bat either. it usually takes profiling to determine where the human-fixable problems are. strictness does not belong in the type system in general. strictness annotations are attached to the data components and not type components in data declarations because they only affect the desugaring of the constructor, but not the run-time representation or the types in general. attaching strictness info to types is just the wrong thing to do in general I think. however, strict tuples I think would have use in function returns, no need to declare them as a separate type, just have (! a,b !) desugar exactly to a `seq` b `seq` (a,b) this avoids any type issues and the only time the strictness of a constructor comes into play is in the constructor desugaring anyway, it makes sense that strict tuples would be a simple desugaring to normal tuples as well. hope this makes sense... John -- John Meacham - ⑆repetae.net⑆john⑈

John Meacham:
On Mon, Mar 20, 2006 at 09:39:41AM -0500, Manuel M T Chakravarty wrote:
Apart from the syntactic issues, does anybody else support the idea of strict tuples as proposed? I just want to know whether I am alone on this before putting it on the wiki.
I have a few issues though, not entirely easy to articulate.
I worry about all the (! .. !) types that will appear in interfaces, making things like (map fst) not work. It has been my experience that a lot of things that should be strict that are obvious to the user, are often obvious to the compiler as well. having the user place redundant strictness annotations in can ofsucate where the actual performance fixes are. As in, are lazy tuples actually a source of problems or are we just guessing? ghc's strictness analyzer is pretty darn good, If something is subtle enough for the compiler not to catch it, then the programmer probably won't right off the bat either. it usually takes profiling to determine where the human-fixable problems are.
I agree that strict tuples can be abused, but that's true for most language features.
strictness does not belong in the type system in general. strictness annotations are attached to the data components and not type components in data declarations because they only affect the desugaring of the constructor, but not the run-time representation or the types in general. attaching strictness info to types is just the wrong thing to do in general I think.
I am *not* proposing any addition or change to the type system. In H98, I can define data Pair a b = Pair a b data StrictPair a b = StrictPair !a !b For some reason, we have Pair with special syntax pre-defined, but we haven't got StrictPair pre-defined. All I am proposing is to also pre-define StrictPair.
however, strict tuples I think would have use in function returns, no need to declare them as a separate type, just have
(! a,b !) desugar exactly to a `seq` b `seq` (a,b)
this avoids any type issues and the only time the strictness of a constructor comes into play is in the constructor desugaring anyway, it makes sense that strict tuples would be a simple desugaring to normal tuples as well.
The disadvantage of this scheme is that the consumer of a strict tuple, then, has no knowledge of the fact that the components are already evaluated - ie, this wastes a good opportunity for optimisations. Manuel

On Tue, Mar 21, 2006 at 02:27:37PM -0500, Manuel M T Chakravarty wrote:
strictness does not belong in the type system in general. strictness annotations are attached to the data components and not type components in data declarations because they only affect the desugaring of the constructor, but not the run-time representation or the types in general. attaching strictness info to types is just the wrong thing to do in general I think.
I am *not* proposing any addition or change to the type system. In H98, I can define
data Pair a b = Pair a b data StrictPair a b = StrictPair !a !b
For some reason, we have Pair with special syntax pre-defined, but we haven't got StrictPair pre-defined. All I am proposing is to also pre-define StrictPair.
yes, but 'StrictPair a b' being a separate type from '(,) a b' is the problem I am refering to. personally, I just really don't see much use for them and feel they will give a false sense of efficiency while only creating headaches. Imagine two uses. f :: (! a,b!) -> Int f (!a, b!) = 3 well, this can better be expressed as f :: (a,b) -> Int f (!a, !b) = 3 and now you can still do things like 'curry f' now, imagine it in return position f :: a -> (! x,y!) f a = (! x, y !) this can better be expressed as f :: a -> (x,y) f a = x `seq` y `seq` (x,y) -- ^ some syntatic sugar for this could be nice If you care enough about some data you are passing around to intimatly know whether it might or might not have bottoms in it, then chances are it is something you want a custom data type for anyway. strict tuples would not really express intent any more and without some sort of subtyping mechanism the hassle of dealing with them would greatly outweigh the questionable benefit. not that people shouldn't create their own 'data StrictPair' if they want. but I would never want to see such a type in any public APIs. It would just not be very friendly.
however, strict tuples I think would have use in function returns, no need to declare them as a separate type, just have
(! a,b !) desugar exactly to a `seq` b `seq` (a,b)
this avoids any type issues and the only time the strictness of a constructor comes into play is in the constructor desugaring anyway, it makes sense that strict tuples would be a simple desugaring to normal tuples as well.
The disadvantage of this scheme is that the consumer of a strict tuple, then, has no knowledge of the fact that the components are already evaluated - ie, this wastes a good opportunity for optimisations.
optimizations for who? knowing something is already evaluated without any other knowledge about it affords no optimizations in the ghc model (but actually does in the jhc one), knowing things will definitily be evaluated certainly does. which strict tuples don't really help with any more than the 'seq' translation would. John -- John Meacham - ⑆repetae.net⑆john⑈

John Meacham wrote:
ghc's strictness analyzer is pretty darn good, If something is subtle enough for the compiler not to catch it, then the programmer probably won't right off the bat either.
Even the best strictness analyzer can't determine that a function is strict when it really isn't. The main point of strictness annotations, I think, is to actually change the denotational semantics of the program.
strictness does not belong in the type system in general. strictness annotations are attached to the data components and not type components in data declarations because they only affect the desugaring of the constructor, but not the run-time representation or the types in general. attaching strictness info to types is just the wrong thing to do in general I think.
Your argument seems circular. Haskell 98 strictness annotations are just sugar, but they didn't *have* to be. You can say that f is strict if f _|_ = _|_, or you can say it's strict if its domain doesn't include _|_ at all. One feels more at home in the value language (seq, ! on constructor fields), the other feels more at home in the type language (! on the left of the function arrow, more generally ! on types to mean lack of _|_). -- Ben
participants (4)
-
Ben Rudiak-Gould
-
John Meacham
-
Manuel M T Chakravarty
-
Simon Marlow