patch applied (haskell-prime-status): BangPatterns: probably accept ==> undecided

Tue Apr 15 11:12:08 PDT 2008 Simon Marlow

simonmarhaskell:
Tue Apr 15 11:12:08 PDT 2008 Simon Marlow
* BangPatterns: probably accept ==> undecided M ./status.hs -2 +3
I think we absolutely must have a story on bang patterns for H'. They're now very widely used in low level code, where we either don't trust, or need to tune, the strictness analyser. And using CPP for this is just not acceptable, and I still cry a little inside when I have to use #define STRICT1(f) f a | a `seq` False = undefined #define STRICT2(f) f a b | a `seq` b `seq` False = undefined #define STRICT3(f) f a b c | a `seq` b `seq` c `seq` False = undefined STRICT2(f) f x y = ... to achieve portability to Hugs/nhc98 of Data.ByteString. In the list of features "required for Haskell in practice", bang patterns are way up there. -- Don

Hello Don, Wednesday, April 16, 2008, 7:06:28 PM, you wrote:
In the list of features "required for Haskell in practice", bang patterns are way up there.
+1. they are also required to achieve good results in various shutouts :D -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi
In the list of features "required for Haskell in practice", bang patterns are way up there.
But their syntax has issues: a!b = ... Did I just define the function "a" or the function "!"? I'm not saying they shouldn't be accepted, but the story should be a little clearer about this as well! Thanks Neil

Hi
a!b = ...
Did I just define the function "a" or the function "!"?
I'm not saying they shouldn't be accepted, but the story should be a little clearer about this as well!
For what it is worth, in discussions with Matt, we wondered if eliminating infix function definition altogether was an option. We decided that you probably don't gain much by defining functions infix, as you have to define their type prefix anyway. Of course you still want to use functions infix, but that is a separate issue. Of course, this can't be done for Haskell', but might make an interesting alternative design. Thanks Neil

On Wed, Apr 16, 2008 at 06:22:14PM +0100, Neil Mitchell wrote:
Hi
In the list of features "required for Haskell in practice", bang patterns are way up there.
But their syntax has issues:
a!b = ...
Did I just define the function "a" or the function "!"?
Interesting note, if we solve this, then we can apply the same thing to the treatment of ~ and regain it as a usable operator. John -- John Meacham - ⑆repetae.net⑆john⑈

| > > In the list of features "required for Haskell in practice", bang patterns are | > > way up there. | > | > But their syntax has issues: | > | > a!b = ... | > | > Did I just define the function "a" or the function "!"? | | Interesting note, if we solve this, then we can apply the same thing to | the treatment of ~ and regain it as a usable operator. In GHC I implemented a pretty grotesque hack. I really really wanted f !x !y = e to work as you'd expect. But because of the infix operator thing, that parses as (f ! x) ! y = e A gruesome post-processing step restores the parse we want, for the special case of !. It's not nice, but I didn't have the luxury of changing anything else, which we do now. Not allowing infix functions on the LHS would be a notable simplification. Constructors in patterns should still be infix of course: f (a :=: b) = ... In any case, I've always thought this was weird: Just x == Just y = x == y Simon

Hi, Simon PJ wrote (Re: BangPatterns: probably accept ==> undecided):
Not allowing infix functions on the LHS would be a notable simplification.
And a little later (Re: Infix type constructors):
What we *want* is to say
data a + b = Left a | Right b
That is, we want to define the type *constructor* (+)
Just to clarify, issues of what names can be used for type constructors aside, are you proposing dropping infix syntax for defining functions, but retaining infix syntax for defining types (and type families etc.)? Or would the last example have to be written data (+) a b = Left a | Right b ? All the best, /Henrik -- Henrik Nilsson School of Computer Science The University of Nottingham nhn@cs.nott.ac.uk This message has been checked for viruses but the contents of an attachment may still contain software viruses, which could damage your computer system: you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation.

| Just to clarify, issues of what names can be used for | type constructors aside, are you proposing dropping | infix syntax for defining functions, but retaining infix | syntax for defining types (and type families etc.)? | | Or would the last example have to be written | | data (+) a b = Left a | Right b I *am* proposing that varsyms become type *constructors* not type *variables*. I can see arguments both ways for allowing definitions in infix form, and I don't have a strong position either way. Simon

Simon Peyton Jones wrote:
Not allowing infix functions on the LHS would be a notable simplification.
This would significantly weaken a useful property of Haskell, that definitions and uses often share the same concrete syntax. It's very natural to be able to define things that way and it would be a real shame to lose it (and I think it would break a lot of existing code).
In any case, I've always thought this was weird: Just x == Just y = x == y
It takes a little getting used to, but I don't find it that weird. I wouldn't mind if just infix definitions of (!) were banned, though of course that would be an unpleasant non-orthogonality. Cheers, Ganesh ============================================================================== Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html ==============================================================================

Am Freitag, 18. April 2008 11:54 schrieb Sittampalam, Ganesh:
Simon Peyton Jones wrote:
Not allowing infix functions on the LHS would be a notable simplification.
This would significantly weaken a useful property of Haskell, that definitions and uses often share the same concrete syntax. It's very natural to be able to define things that way and it would be a real shame to lose it (and I think it would break a lot of existing code).
+1 (f . g) x = f (g x) is really nice.
In any case, I've always thought this was weird: Just x == Just y = x == y
It takes a little getting used to, but I don't find it that weird.
+1
[…]
Best wishes, Wolfgang

On Fri, Apr 18, 2008 at 08:36:42AM +0100, Simon Peyton-Jones wrote:
Not allowing infix functions on the LHS would be a notable simplification. Constructors in patterns should still be infix of course: f (a :=: b) = ...
I don't know, I think this will confuse things, especially for newbies, people tend to say things like: a + b = foo as "a plus b is foo", and so would probably naturally write it in infix form, it would be a source of confusion if the compiler didn't accept it. I don't think saying ~ and ! are operators unless they 1. immediately followed by a '(', a letter, or an underscore 2. are preceded by whitespace or BOL is that onerous. John -- John Meacham - ⑆repetae.net⑆john⑈

John Meacham wrote:
On Fri, Apr 18, 2008 at 08:36:42AM +0100, Simon Peyton-Jones wrote:
Not allowing infix functions on the LHS would be a notable simplification. Constructors in patterns should still be infix of course: f (a :=: b) = ...
I don't know, I think this will confuse things, especially for newbies, people tend to say things like:
a + b = foo
as "a plus b is foo", and so would probably naturally write it in infix form, it would be a source of confusion if the compiler didn't accept it.
I don't think saying ~ and ! are operators unless they
1. immediately followed by a '(', a letter, or an underscore 2. are preceded by whitespace or BOL
is that onerous.
I don't like the idea of solving this in the lexical syntax, e.g. by the rules you gave above, it's just too ad-hoc. I think a better way to fix it is just to disallow infix declarations of !, ~ (and @ ?). Currently the grammar has: funlhs -> var apat {apat} | pati+1 varop(a,i) pati+1 | lpati varop(l,i) pati+1 | pati+1 varop(r,i) rpati | ( funlhs ) apat {apat} so we can use a restricted variant of varop that doesn't include !, ~ or @ (well, varop doesn't currently include ~ or @, but I assume we want it to - it would be similar to the way "hiding" is handled now). Incedentally I think we should use a different operator for array indexing, because ! is almost universally used to mean "strict" now: in bang patterns, strict datatype fields, and $!. See http://hackage.haskell.org/trac/haskell-prime/wiki/ArrayIndexing Cheers, Simon

Incedentally I think we should use a different operator for array indexing, because ! is almost universally used to mean "strict" now: in bang patterns, strict datatype fields, and $!. See
http://hackage.haskell.org/trac/haskell-prime/wiki/ArrayIndexing
A lot of the discussion on that page pre-supposes that CompositionAsDot will be accepted. Does it really stand a chance? It would be enormously disruptive and uglify the language massively. Making it necessary to use non-ASCII characters would be a big practical problem, I think. Ganesh ============================================================================== Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html ==============================================================================

Sittampalam, Ganesh wrote:
Incedentally I think we should use a different operator for array indexing, because ! is almost universally used to mean "strict" now: in bang patterns, strict datatype fields, and $!. See
http://hackage.haskell.org/trac/haskell-prime/wiki/ArrayIndexing
A lot of the discussion on that page pre-supposes that CompositionAsDot will be accepted. Does it really stand a chance? It would be enormously disruptive and uglify the language massively. Making it necessary to use non-ASCII characters would be a big practical problem, I think.
Here are the possibilities for composition: 0. do nothing 1. use a Unicode operator for composition 2. require spaces around . as an operator 3. require spaces around all operators 4. use another ASCII operator for composition, e.g. <<< Nothing has been decided yet, but most of the committee tends to favour (2), with some expressing a slight preference for (0). We've pretty much ruled out (1) and (3) as too radical, and as you say using Unicode is still too impractical. There is some uncertainty about the precise details of (2), and thinking about that is what lead to my proposal about changing the syntax of qualified operators. Cheers, Simon

On Mon, Apr 21, 2008 at 01:36:33PM -0700, Simon Marlow wrote:
0. do nothing 1. use a Unicode operator for composition 2. require spaces around . as an operator 3. require spaces around all operators 4. use another ASCII operator for composition, e.g. <<<
Nothing has been decided yet, but most of the committee tends to favour (2), with some expressing a slight preference for (0). We've pretty much ruled out (1) and (3) as too radical, and as you say using Unicode is still too impractical.
There is also the proposal to change the fixity of '$'. this would mean that '.' becomes a lot more common as f $ a $ b $ c would now be written f . a . b $ c John -- John Meacham - ⑆repetae.net⑆john⑈

Am Dienstag, 22. April 2008 01:58 schrieb John Meacham:
[…]
There is also the proposal to change the fixity of '$'.
Why should the fixity of $ being changed? I thought, the reason for $ was that you can write a $ b $ c.
[…]
Best wishes, Wolfgang

2008/4/24 Wolfgang Jeltsch
Am Dienstag, 22. April 2008 01:58 schrieb John Meacham: Why should the fixity of $ being changed? I thought, the reason for $ was that you can write a $ b $ c.
Well, the reasons for this were discussed on another thread recently, but in brief, you can always rewrite "f $ g $ h $ x" as "f . g . h $ x", whereas there's no way to remove the parentheses from expressions like "f (g x) (h y) (k z)", which, if ($) were left associative like function application normally is, could be written "f $ g x $ h y $ k z". Moreover, using function composition in place of ($) where possible should probably be considered better style regardless, as expressions written that way effectively have more subexpressions, because (.) is an associative operator. For instance, in "f $ g $ h $ x", the substring "g $ h" is meaningless, but in "f . g . h $ x", we have that "g . h" is a well-typed function, as well as "f . g". Another good reason is that we certainly wouldn't want ($!) to have a different associativity than ($), and the left-associative form of ($!) is far more useful than the present right-associative one. Strictly applying a function to any parameter but the last currently requires awkward parentheses. In combination with left-associating ($), a left-associating ($!) will allow any combination of strict applications to be easily expressed. I tend to think of the present associativity of ($) as a kind of oversight which people started to abuse in place of proper function composition, whereas the alternate associativity has real benefits over this one. - Cale

Simon Marlow wrote:
Here are the possibilities for composition:
0. do nothing 1. use a Unicode operator for composition 2. require spaces around . as an operator 3. require spaces around all operators 4. use another ASCII operator for composition, e.g. <<<
Nothing has been decided yet, but most of the committee tends to favour (2), with some expressing a slight preference for (0). We've pretty much ruled out (1) and (3) as too radical, and as you say using Unicode is still too impractical.
There is some uncertainty about the precise details of (2), and thinking about that is what lead to my proposal about changing the syntax of qualified operators.
Ok, I'm going to try to make some progress on this. I think it's fair to say that the only possible options are (0) do nothing, or (2) require spaces around "." as an operator. I'll explore how we might do (2). We discussed this a bit on the committee mailing list, here's where we got to. The proposal amounts to making certain sequences illegal. Let's try to implement the informal rule dot is only allowed adjacent to a varid or conid when it is part of a qualified name so that would make these illegal: length.lines (.f) (f.) ++.x x.++ Just.(+1) Here's an interesting case: [Monday..Friday] which I imagine we would like to be legal. (currently it's illegal, or rather 'Monday..' is interpreted as a qualified operator; see separate proposal for changing the syntax of qualified operators). The way to implement this is to add the following productions to the lexical syntax: reservedlexeme ::= ({symbol} '.')<reservedop> (varid | conid) | (varid | conid) ('.' {symbol})<reservedop> The idea is that reservedlexemes are illegal, and work via the maximal-munch rule. (note that this version relies on the alternate qualified operator syntax proposal, because it makes the existing qualified operator syntax into a reservedlexeme). My personal view is that this is somewhat ugly. However, it does have the benefit of releasing the 'foo.x' syntax for future use, e.g. in a new record system - but some people find that a bit tasteless too, and I might be inclined to agree. Thoughts? Cheers, Simon

On Mon, Apr 28, 2008 at 10:39:09AM -0700, Simon Marlow wrote:
Ok, I'm going to try to make some progress on this. I think it's fair to say that the only possible options are (0) do nothing, or (2) require spaces around "." as an operator.
If we are considering requiring spaces around "." then I think it would make sense to also consider requiring spaces around * "-" (so we can make "-2" and "map (- 3) xs" both do what you expect) * "!" (meaning that "f !x" isn't valid but differently parsed for patterns and expressions - assuming we plan to accept BangPatterns). I don't think it makes sense to make a special case for requiring spaces around "$", as TH won't be in H'. Thanks Ian

I don't think it makes sense to make a special case for requiring spaces around "$", as TH won't be in H'.
I agree, there's absolutely no need to treat $ differently in H'. The situation will already be better than it is now, since by the special treatment of . (and - and !, which I also agree with), there will be a precedent to follow (assuming it gets accepted of course). That alone makes it much easier to define the meaning of extensions like $ in TH. Cheers, /Niklas

Simon Marlow wrote:
Simon Marlow wrote:
Here are the possibilities for composition:
0. do nothing 1. use a Unicode operator for composition 2. require spaces around . as an operator 3. require spaces around all operators 4. use another ASCII operator for composition, e.g. <<<
Ok, I'm going to try to make some progress on this. I think it's fair to say that the only possible options are (0) do nothing, or (2) require spaces around "." as an operator.
Yesterday I talked to John Launchbury, who had previously been strongly opposed to option (0), and we noticed that the proposed change to the syntax of qualified operators actually negates some of the concerns about dot. The H98 report lists these examples: f.g f . g (three tokens) F.g F.g (qualified `g') f.. f .. (two tokens) ***** F.. F.. (qualified `.') F. F . (two tokens) that with the qualified operator change, this becomes: f.g f . g (three tokens) F.g F.g (qualified `g') f.(.) f . (.) (three tokens) ***** F.(.) F.(.) (qualified `.') F. F . (two tokens) look at the example marked with *****. With the new syntax it is no longer a weird exception: 'f..' is two tokens, whereas 'f.(.)' is three tokens just like 'f.g'. The syntax is more regular. John tells me he's happy to go with option (0) - make no other changes to dot - as long as we adopt the qualified operator change. I'm comfortable with that position too. Cheers, Simon

On Tue, Apr 29, 2008 at 02:05:58PM -0700, Simon Marlow wrote:
that with the qualified operator change, this becomes:
f.g f . g (three tokens) F.g F.g (qualified `g') f.(.) f . (.) (three tokens) ***** F.(.) F.(.) (qualified `.') F. F . (two tokens)
And [f..], [F..] etc will parse as we want them to too. Sounds OK to me. Thanks Ian
participants (13)
-
Bulat Ziganshin
-
Cale Gibbard
-
Don Stewart
-
Henrik Nilsson
-
Ian Lynagh
-
John Meacham
-
Neil Mitchell
-
Niklas Broberg
-
Simon Marlow
-
Simon Marlow
-
Simon Peyton-Jones
-
Sittampalam, Ganesh
-
Wolfgang Jeltsch