Bang patterns

Ian Lynagh ian at well-typed.com
Fri Feb 1 18:10:42 CET 2013


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




More information about the Haskell-prime mailing list