
Hi all, I would like to get a full specification of the bang patterns syntax, partly so it can be proposed for H', and partly so we can resolve tickets like http://hackage.haskell.org/trac/ghc/ticket/1087 correctly. I think there are 3 possibilities: The first is suggested by "A bang only really has an effect if it precedes a variable or wild-card pattern" on http://hackage.haskell.org/trac/haskell-prime/wiki/BangPatterns We could therefore alter the lexical syntax to make strict things into lexems, for example reservedid -> ... | _ | !_ strictvarid -> ! varid etc. This would mean that "f !x" is 2 lexemes, and "f ! x" 3 lexemes, with the former defining the function 'f' and the latter defining the operator '!'. This has 3 downsides: * It would require also accepting the more radical proposal of making let strict, as it would no longer be possible to write let ![x,y] = undefined in () * It would mean that "f !x" and "f !(x)" are different. Probably not a big issue in practice. * It may interact badly with other future extensions. For example, {-# LANGUAGE ViewPatterns #-} f !(view -> x) = () should arguably be strict in x. (you might also argue that it should define the operator '!'. Currently, in ghc, it defines an 'f' that is lazy in x, which IMO is a bug). The second is to parse '!' differently depending on whether or not it is followed by a space. In the absence of a decision to require infix operators to be surrounded by spaces, I think this is a bad idea: Tricky to specify, and to understand. The third is to parse '!' in patterns in the same way that '~' is parsed in patterns, except that (!) would be accepted as binding the operator '!'. This means that "f ! x" defines f. So my proposal would be to go with option 3. What do you think? And did I miss any better options? Thanks Ian

On Fri, Feb 01, 2013 at 05:10:42PM +0000, Ian Lynagh wrote:
The first is suggested by "A bang only really has an effect if it precedes a variable or wild-card pattern" on http://hackage.haskell.org/trac/haskell-prime/wiki/BangPatterns
We could therefore alter the lexical syntax to make strict things into lexems, for example reservedid -> ... | _ | !_ strictvarid -> ! varid etc. This would mean that "f !x" is 2 lexemes, and "f ! x" 3 lexemes, with the former defining the function 'f' and the latter defining the operator '!'.
This has 3 downsides:
* It would require also accepting the more radical proposal of making let strict, as it would no longer be possible to write let ![x,y] = undefined in ()
We really can't make let strict, in my view: its laziness is sort of fundamental. I don't see why the given example necessitates it though: just use case-of in that scenario. In fact, I've kind of always been uncomfortable with bang patterns in let-statements. I feel like I should be able to omit an unused let-binding without affecting my program at all, and bang patterns in let make that no longer true.
* It would mean that "f !x" and "f !(x)" are different. Probably not a big issue in practice.
Yeah, I'm not upset about this. We'd be thinking of the ! as a decorator in the same way that, say, infix-backticks are: we don't expect `(foo)` to work.
* It may interact badly with other future extensions. For example, {-# LANGUAGE ViewPatterns #-} f !(view -> x) = () should arguably be strict in x. (you might also argue that it should define the operator '!'. Currently, in ghc, it defines an 'f' that is lazy in x, which IMO is a bug).
Hmm. Not quite strict in x. I'd think the right way to make that strict in x is: f (view -> !x) = () What you want is possibly to evaluate the thing you pass to the view /before/ matching on the result. But I imagine that in most cases your view function will be strict so the difference will be immaterial. I agree that GHC current behaviour looks like a bug.
The second is to parse '!' differently depending on whether or not it is followed by a space. In the absence of a decision to require infix operators to be surrounded by spaces, I think this is a bad idea: Tricky to specify, and to understand.
Hmm. It's a shame because in real code operator definitions are almost invariably surrounded by spaces, even when the use of the operator wouldn't be. But I agree in general.
The third is to parse '!' in patterns in the same way that '~' is parsed in patterns, except that (!) would be accepted as binding the operator '!'. This means that "f ! x" defines f.
This is roughly how it's done at present, right? It's annoyingly inconsistent, but fairly low-impact.
So my proposal would be to go with option 3. What do you think? And did I miss any better options?
You missed the option of going the way of ~ and making ! an illegal name for an operator. Obvious drawbacks, probably not a good idea, but it would be the most consistent solution, so I wouldn't dismiss it immediately. (If we do come up with a way that doesn't involve making ! illegal, maybe we should consider allowing ~ as an operator as well!) There's another alternative entirely, that I haven't really thought about: introduce bang patterns on types instead of on variables. I realise this is less flexible, but! it covers many common cases, it avoids the infix confusion altogether, it echoes the existing usage for strict datatypes, and it makes the strictness of a function (potentially) part of its type signature, which would be handy in documentation. I realise this is a bit late in the game to be including this option, but if it doesn't get thought about now, it never will. Anyway, in light of my above comments, I think I like the first option the best (so bang patterns only apply to variables, let doesn't become strict). regards, Ben

On Sun, Feb 03, 2013 at 10:34:04PM +0000, Ben Millwood wrote:
On Fri, Feb 01, 2013 at 05:10:42PM +0000, Ian Lynagh wrote:
The first is suggested by "A bang only really has an effect if it precedes a variable or wild-card pattern" on http://hackage.haskell.org/trac/haskell-prime/wiki/BangPatterns
We could therefore alter the lexical syntax to make strict things into lexems, for example reservedid -> ... | _ | !_ strictvarid -> ! varid etc. This would mean that "f !x" is 2 lexemes, and "f ! x" 3 lexemes, with the former defining the function 'f' and the latter defining the operator '!'.
This has 3 downsides:
* It would require also accepting the more radical proposal of making let strict, as it would no longer be possible to write let ![x,y] = undefined in ()
We really can't make let strict, in my view: its laziness is sort of fundamental. I don't see why the given example necessitates it though: just use case-of in that scenario.
Well, true, that's another option. It's rather unpleasant when you have multiple bindings, as when converted to 'case's, each 'case' requires you to indent deeper (or to use more braces).
The third is to parse '!' in patterns in the same way that '~' is parsed in patterns, except that (!) would be accepted as binding the operator '!'. This means that "f ! x" defines f.
This is roughly how it's done at present, right?
I think it's roughly what GHC does now, yes.
You missed the option of going the way of ~ and making ! an illegal name for an operator. Obvious drawbacks, probably not a good idea, but it would be the most consistent solution, so I wouldn't dismiss it immediately.
Yes, OK. That's basically option 3 as far as patterns are concerned, but also disallows ! as an operator.
(If we do come up with a way that doesn't involve making ! illegal, maybe we should consider allowing ~ as an operator as well!)
Right, if we went for option 3 then making ~ an operator in the same way as ! would be possible. I think we should be cautious about doing so, though, as it's a semi-one-way change, i.e. once it's an operator and people start using it it becomes a lot trickier to revert the decision.
Anyway, in light of my above comments, I think I like the first option the best (so bang patterns only apply to variables, let doesn't become strict).
So just to clarify what you're proposing, this wouldn't be valid: let ![x] = e in ... and I guess these wouldn't either?: let !x = e in ... let [!x] = e in ... let (x, ~(y, !z)) = e in ... but these would?: let f !x = e in ... case x of ~(y, !z) -> () i.e. you wouldn't be able to use ! in the 'pat' in the decl -> pat rhs production. You'd also no longer support: do ![x] <- e; ... and so again for consistency I guess these wouldn't work?: do !x <- e; ... do [!x] <- e; ... do (x, ~(y, !z)) <- e; ... i.e. you also wouldn't be able to use ! in the 'pat' in the stmt -> pat <- exp ; production. Thanks Ian

On Sun, Feb 03, 2013 at 11:22:12PM +0000, Ian Lynagh wrote:
On Sun, Feb 03, 2013 at 10:34:04PM +0000, Ben Millwood wrote:
On Fri, Feb 01, 2013 at 05:10:42PM +0000, Ian Lynagh wrote:
The first is suggested by "A bang only really has an effect if it precedes a variable or wild-card pattern" on http://hackage.haskell.org/trac/haskell-prime/wiki/BangPatterns
We could therefore alter the lexical syntax to make strict things into lexems, for example reservedid -> ... | _ | !_ strictvarid -> ! varid etc. This would mean that "f !x" is 2 lexemes, and "f ! x" 3 lexemes, with the former defining the function 'f' and the latter defining the operator '!'.
This has 3 downsides:
* It would require also accepting the more radical proposal of making let strict, as it would no longer be possible to write let ![x,y] = undefined in ()
We really can't make let strict, in my view: its laziness is sort of fundamental. I don't see why the given example necessitates it though: just use case-of in that scenario.
Well, true, that's another option. It's rather unpleasant when you have multiple bindings, as when converted to 'case's, each 'case' requires you to indent deeper (or to use more braces).
Yes, or you could use a tuple, or you could use seq directly, but I recognise those options as having their own drawbacks. (Observation: if bang patterns are made primitive, seq can be implemented as an ordinary function in terms of them.)
(If we do come up with a way that doesn't involve making ! illegal, maybe we should consider allowing ~ as an operator as well!)
Right, if we went for option 3 then making ~ an operator in the same way as ! would be possible. I think we should be cautious about doing so, though, as it's a semi-one-way change, i.e. once it's an operator and people start using it it becomes a lot trickier to revert the decision.
Yeah, I wouldn't be overeager to do it, just worth remembering that that option becomes open.
Anyway, in light of my above comments, I think I like the first option the best (so bang patterns only apply to variables, let doesn't become strict).
So just to clarify what you're proposing, this wouldn't be valid: let ![x] = e in ... and I guess these wouldn't either?: let !x = e in ... let [!x] = e in ... let (x, ~(y, !z)) = e in ... but these would?: let f !x = e in ... case x of ~(y, !z) -> ()
I have two proposals, I suppose: - make bang patterns operate only on variables and wildcards - make bang patterns in let altogether invalid (with an optional third, "make bang patterns something else entirely") with the justification for the first being that it is the most common case and interferes less with the infix operator !, and the justification for the second being the somewhat weedier general notion that I think unused let bindings should be discardable, and that I think bang-lets confuse the distinction between case and let (but then, arguably ~ already does that). So, my proposal is the following definitely ARE allowed:
let f !x = e in ... case x of ~(y, !z) -> ()
The following definitely AREN'T:
let ![x] = e in ... do ![x] <- e; ...
but the following are allowed by the first proposal but disallowed by the second:
let !x = e in ... let [!x] = e in ... let (x, ~(y, !z)) = e in ... do !x <- e; ... do [!x] <- e; ... do (x, ~(y, !z)) <- e; ...
I'm not committed to this plan. I can see especially why the second pattern on my forbidden list might be useful. But I don't like making operator-! special. (I still think types might be the right place to put this information). Thanks, Ben

On Mon, Feb 04, 2013 at 12:44:53AM +0000, Ben Millwood wrote:
I have two proposals, I suppose: - make bang patterns operate only on variables and wildcards - make bang patterns in let altogether invalid
Looking at this again made me realise that, as well as !_ and !varid lexemes, we could also alter the decl production so that we get decl -> ... | pat rhs -- existing lazy binding production | '!' pat rhs -- new strict binding production That means that let !(x, y) = e in ... would still be valid, with the ! not actually being parsed as part of the pattern, but would parse instead as a strict binding. It would be a little ugly under the hood, as let !x = e in ... would parse as a lazy binding, although we'd want to treat it as a strict binding anyway. Thanks Ian

| > I have two proposals, I suppose: | > - make bang patterns operate only on variables and wildcards | > - make bang patterns in let altogether invalid | | Looking at this again made me realise that, as well as !_ and !varid | lexemes, we could also alter the decl production so that we get | decl -> ... | | pat rhs -- existing lazy binding production | | '!' pat rhs -- new strict binding production | | That means that | let !(x, y) = e in ... | would still be valid, with the ! not actually being parsed as part of | the pattern, but would parse instead as a strict binding. Yes, I like this. You could see the '!' pat rhs production as cancelling the implied '~' that a let-binding usually gets (see the desugaring for lets in the report). A bang really only makes sense * At the top of a let, to cancel the implied '~'. Like Johan I am very strongly in favour of using ! for this purpose. * On a varid or '_', which otherwise match lazily Hence Ian's proposal, which treats these two separately, makes sense. For example, there's no point in the pattern (x, !(y,z)), because it behaves identically to (x, (y,z)). We really do need to allow f !x y !z = e to mean f is strict in x and z. There is an ambiguity here with a infix definition of (!), but it must be resolved in favour of the bang-pattern version. I don't have a strong opinion about whether f ! x y ! z = e should mean the same; ie whether the space is significant. I think it's probably more confusing if the space is significant (so its presence or absence makes a difference). Simon

On Mon, Feb 04, 2013 at 10:37:44PM +0000, Simon Peyton-Jones wrote:
I don't have a strong opinion about whether f ! x y ! z = e should mean the same; ie whether the space is significant. I think it's probably more confusing if the space is significant (so its presence or absence makes a difference).
I also don't feel strongly, although I lean the other way: I don't think anyone writes "f ! x" when they mean "f with a strict argument x", and I don't see any particular advantage in allowing it. In fact, I think writing that is less clear than "f !x", so there is an advantage in disallowing it. It also means that existing code that defines a (!) operator in infix style would continue to work, provided it puts whitespace around the !. Thanks Ian

If space sensitivity or () disambiguation is being used on !, could one of
these also be permitted on ~ to permit it as a valid infix term-level
operator?
That would be an amazingly valuable symbol to be able to reclaim for the
term level for equivalences, and for folks who come from other languages
where it is used like liftA2 (,) in parsing libraries, etc.
-Edward
On Mon, Feb 4, 2013 at 6:42 PM, Ian Lynagh
On Mon, Feb 04, 2013 at 10:37:44PM +0000, Simon Peyton-Jones wrote:
I don't have a strong opinion about whether f ! x y ! z = e should mean the same; ie whether the space is significant. I think
it's probably more confusing if the space is significant (so its presence or absence makes a difference).
I also don't feel strongly, although I lean the other way:
I don't think anyone writes "f ! x" when they mean "f with a strict argument x", and I don't see any particular advantage in allowing it. In fact, I think writing that is less clear than "f !x", so there is an advantage in disallowing it.
It also means that existing code that defines a (!) operator in infix style would continue to work, provided it puts whitespace around the !.
Thanks Ian
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

On Mon, Feb 04, 2013 at 07:26:16PM -0500, Edward Kmett wrote:
If space sensitivity or () disambiguation is being used on !, could one of these also be permitted on ~ to permit it as a valid infix term-level operator?
I don't think there's any reason ~ couldn't be an operator, defined with the (~) x y = ... syntax. Allowing it to be defined with infix syntax would be a little trickier. Hmm, I've just realised that if we decide to make !_ and !foo lexemes, then we'd also want !(+) to be a lexeme, which presumably means we'd want (+) to be a single lexeme too (and also `foo`, for consistency). But I don't think making that change would be problematic. Thanks Ian

On the topic of liberalizing operators that are currently only used in
patterns, another one that would be amazing to have as a valid term (or
type operator) is @ using similar () tricks. 1 character operator names are
in dreadful short supply and really help make nice DSLs.
-Edward
On Tue, Feb 5, 2013 at 8:42 AM, Ian Lynagh
On Mon, Feb 04, 2013 at 07:26:16PM -0500, Edward Kmett wrote:
If space sensitivity or () disambiguation is being used on !, could one of these also be permitted on ~ to permit it as a valid infix term-level operator?
I don't think there's any reason ~ couldn't be an operator, defined with the (~) x y = ... syntax.
Allowing it to be defined with infix syntax would be a little trickier.
Hmm, I've just realised that if we decide to make !_ and !foo lexemes, then we'd also want !(+) to be a lexeme, which presumably means we'd want (+) to be a single lexeme too (and also `foo`, for consistency). But I don't think making that change would be problematic.
Thanks Ian
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

On 04/02/13 23:42, Ian Lynagh wrote:
On Mon, Feb 04, 2013 at 10:37:44PM +0000, Simon Peyton-Jones wrote:
I don't have a strong opinion about whether f ! x y ! z = e should mean the same; ie whether the space is significant. I think it's probably more confusing if the space is significant (so its presence or absence makes a difference).
I also don't feel strongly, although I lean the other way:
I don't think anyone writes "f ! x" when they mean "f with a strict argument x", and I don't see any particular advantage in allowing it. In fact, I think writing that is less clear than "f !x", so there is an advantage in disallowing it.
It also means that existing code that defines a (!) operator in infix style would continue to work, provided it puts whitespace around the !.
FWIW, I really dislike whitespace-significant syntax. f ! x should mean the same as f !x. Look at the trouble we have with qualified operators: how many people have tried to write [Monday..] and been surprised that it doesn't work? So I don't mind at all if BangPatterns makes it harder to write a definition of '!', because it's much more common to write bang patterns than it is to define '!', and the workaround of writing (!) is not that onerous. Aside from preferring not to change the lexical syntax, I don't have a strong opinion. Your original third option, treating ! and ~ the same way, looks ok to me, but I also like the idea of only allowing bang patterns where they make sense (variables and pattern bindings). Cheers, Simon

On 7 Feb, 2013, at 13:24 , Simon Marlow
On 04/02/13 23:42, Ian Lynagh wrote:
On Mon, Feb 04, 2013 at 10:37:44PM +0000, Simon Peyton-Jones wrote:
I don't have a strong opinion about whether f ! x y ! z = e should mean the same; ie whether the space is significant. I think it's probably more confusing if the space is significant (so its presence or absence makes a difference).
I also don't feel strongly, although I lean the other way:
I don't think anyone writes "f ! x" when they mean "f with a strict argument x", and I don't see any particular advantage in allowing it. In fact, I think writing that is less clear than "f !x", so there is an advantage in disallowing it.
It also means that existing code that defines a (!) operator in infix style would continue to work, provided it puts whitespace around the !.
FWIW, I really dislike whitespace-significant syntax. f ! x should mean the same as f !x. Look at the trouble we have with qualified operators: how many people have tried to write [Monday..] and been surprised that it doesn't work?
So I don't mind at all if BangPatterns makes it harder to write a definition of '!', because it's much more common to write bang patterns than it is to define '!', and the workaround of writing (!) is not that onerous.
I agree, I prefer the invariant that lexically whitespace does not matter. It is easier to understand, implement, and it is not such a big deal to have the choice of meaning (i.e. bang pattern or infix operator) depend on a LANGUAGE pragma, (re)defining ! is not that common anyway. cheers, - Atze - Atze Dijkstra, Department of Information and Computing Sciences. /|\ Utrecht University, PO Box 80089, 3508 TB Utrecht, Netherlands. / | \ Tel.: +31-30-2534118/1454 | WWW : http://www.cs.uu.nl/~atze . /--| \ Fax : +31-30-2513971 .... | Email: atze@uu.nl ............... / |___\

On Thu, Feb 07, 2013 at 12:24:48PM +0000, Simon Marlow wrote:
FWIW, I really dislike whitespace-significant syntax. f ! x should mean the same as f !x. Look at the trouble we have with qualified operators: how many people have tried to write [Monday..] and been surprised that it doesn't work?
What about `elem`? I don't think anyone would argue that ` elem ` makes sense.

On 08/02/13 11:49, Ben Millwood wrote:
On Thu, Feb 07, 2013 at 12:24:48PM +0000, Simon Marlow wrote:
FWIW, I really dislike whitespace-significant syntax. f ! x should mean the same as f !x. Look at the trouble we have with qualified operators: how many people have tried to write [Monday..] and been surprised that it doesn't work?
What about `elem`? I don't think anyone would argue that ` elem ` makes sense.
Prelude> 1 ` elem ` [1..10] True Prelude> 1 ` {- comment -} elem ` [1..10] True backticks are part of the context-free syntax, not the lexical syntax (as they should be!). I'm of the opinion that the lexical syntax should be as simple, and as far as possible everything should be pushed into the context-free syntax. Cheers, Simon

I prefer them to be part of the context-free syntax, since this enables a future extension in which an arbitary expression can be placed between backticks. This would enable one to write things as:
x `f i` y
and
expr1 `expr2` expr3
is to be interpreted as (expr2) (expr1) (expr3),
Doaitse
On Feb 8, 2013, at 13:27 , Simon Marlow
On 08/02/13 11:49, Ben Millwood wrote:
On Thu, Feb 07, 2013 at 12:24:48PM +0000, Simon Marlow wrote:
FWIW, I really dislike whitespace-significant syntax. f ! x should mean the same as f !x. Look at the trouble we have with qualified operators: how many people have tried to write [Monday..] and been surprised that it doesn't work?
What about `elem`? I don't think anyone would argue that ` elem ` makes sense.
Prelude> 1 ` elem ` [1..10] True Prelude> 1 ` {- comment -} elem ` [1..10] True
backticks are part of the context-free syntax, not the lexical syntax (as they should be!). I'm of the opinion that the lexical syntax should be as simple, and as far as possible everything should be pushed into the context-free syntax.
Cheers, Simon
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

On Sun, Feb 3, 2013 at 4:44 PM, Ben Millwood
I have two proposals, I suppose: - make bang patterns in let altogether invalid
I would prefer it to be valid. It's the syntactically most lightweight option we have to force some thunks before using the resulting values in a constructor that we have. Example let !x = ... !y = ... in C x y The alternative would be let x = ... y = ... in x `seq` y `seq` C x y which obscures the code much more. My 2 cents. -- Johan

On Mon, Feb 04, 2013 at 01:21:31PM -0800, Johan Tibell wrote:
On Sun, Feb 3, 2013 at 4:44 PM, Ben Millwood
wrote: I have two proposals, I suppose: - make bang patterns in let altogether invalid
I would prefer it to be valid. It's the syntactically most lightweight option we have to force some thunks before using the resulting values in a constructor that we have. Example
let !x = ... !y = ... in C x y
The alternative would be
let x = ... y = ... in x `seq` y `seq` C x y
which obscures the code much more.
I'd write (C $! x) $! y. We could devise a left-associative $! to avoid the use of parentheses here. But my objection was only ever a mild unease in any case, so I'm happy to dismiss it. Ben
participants (8)
-
Atze Dijkstra
-
Ben Millwood
-
Doaitse Swierstra
-
Edward Kmett
-
Ian Lynagh
-
Johan Tibell
-
Simon Marlow
-
Simon Peyton-Jones