Re: Bang patterns

2013-02-08 Thread Ben Millwood

On Thu, Feb 07, 2013 at 12:24:48PM +, 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.


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Bang patterns

2013-02-08 Thread Doaitse Swierstra
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 marlo...@gmail.com
 wrote:

 On 08/02/13 11:49, Ben Millwood wrote:
 On Thu, Feb 07, 2013 at 12:24:48PM +, 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


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Bang patterns

2013-02-07 Thread Simon Marlow

On 04/02/13 23:42, Ian Lynagh wrote:

On Mon, Feb 04, 2013 at 10:37:44PM +, 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


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Bang patterns

2013-02-07 Thread Atze Dijkstra

On  7 Feb, 2013, at 13:24 , Simon Marlow marlo...@gmail.com wrote:

 On 04/02/13 23:42, Ian Lynagh wrote:
 On Mon, Feb 04, 2013 at 10:37:44PM +, 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: a...@uu.nl ... /   |___\




___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Bang patterns

2013-02-05 Thread 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


Re: Bang patterns

2013-02-05 Thread Edward Kmett
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 i...@well-typed.com wrote:

 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

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Bang patterns

2013-02-04 Thread Johan Tibell
On Sun, Feb 3, 2013 at 4:44 PM, Ben Millwood hask...@benmachine.co.uk 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.

My 2 cents.

-- Johan

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


RE: Bang patterns

2013-02-04 Thread Simon Peyton-Jones
|   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



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Bang patterns

2013-02-04 Thread Ian Lynagh
On Mon, Feb 04, 2013 at 10:37:44PM +, 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


Re: Bang patterns

2013-02-04 Thread Ben Millwood

On Mon, Feb 04, 2013 at 01:21:31PM -0800, Johan Tibell wrote:

On Sun, Feb 3, 2013 at 4:44 PM, Ben Millwood hask...@benmachine.co.uk 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

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Bang patterns

2013-02-04 Thread Edward Kmett
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 i...@well-typed.com wrote:

 On Mon, Feb 04, 2013 at 10:37:44PM +, 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

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Bang patterns

2013-02-03 Thread Ben Millwood

On Fri, Feb 01, 2013 at 05:10:42PM +, 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

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Bang patterns

2013-02-03 Thread Ian Lynagh
On Sun, Feb 03, 2013 at 10:34:04PM +, Ben Millwood wrote:
 On Fri, Feb 01, 2013 at 05:10:42PM +, 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


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Bang patterns

2013-02-01 Thread Ian Lynagh

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


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Suggestion for bang patterns documentation

2009-02-27 Thread Christian Maeder
Brian Bloniarz wrote:
 I got confused by the GHC documentation recently, I was wondering how
 it could be improved. From:
 http://www.haskell.org/ghc/docs/latest/html/users_guide/bang-patterns.html

Seeing the rule
 pat ::= !pat

you'll probably want to avoid patterns like: !!pat, ! ! pat, or ~ !
~ pat.

Even the current http://www.haskell.org/onlinelibrary/exps.html#sect3.17.1

  apat - ~ apat

allows ~ ~x. (Note the space!) So maybe a separate non-terminal bpat
should be used with:

 bpat - [~|!] apat

(and bpat used within pat). You may also want to exclude v@ ~(...) in
favor of ~v@(...).

 A bang only really has an effect if it precedes a variable or wild-card 
 pattern:
 f3 !(x,y) = [x,y]
 f4 (x,y)  = [x,y]
 Here, f3 and f4 are identical; putting a bang before a pattern that
 forces evaluation anyway does nothing.

Maybe the duality (if it is one) should be added that an irrefutable
pattern above would make a difference but not within the let below.

 The first sentence is true, but only in settings where the pattern is being
 evaluated eagerly -- the bang in:
 f3 a = let !(x,y) = a in [1,x,y]
 f4 a = let (x,y) = a in [1,x,y]
 has an effect.

Cheers Christian

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Consistency of reserved operators and bang patterns

2007-09-08 Thread Neil Mitchell
Hi

Re ! as an operator: This caused a number of complexities in the
parsing of stuff, including shift-reduce conflicts. Someone would need
to look into this, and determine that the rules are completely
unambiguous.

  Backwards compatibility requires that it be implicitly imported from
  Prelude even in a module that does import Prelude ( ) (although Hugs
  is already broken in this regard).

 In particular, Haskell-98 bans

 import Prelude ( (:) )

Yhc does not meet this restriction either. Perhaps this is a change
that is breaking but minor enough to be permitted for H', since
everyone already does the reverse.

Thanks

Neil
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Consistency of reserved operators and bang patterns

2007-09-07 Thread Twan van Laarhoven
The bang pattern proposal [1] still allows (!) to be used as an 
operator. I think there should be no difference in this regard between ! 
and ~, since they are used in exactly the same location.


In my opinion the best thing would be to allow (~) and (@) as operators. 
With the same restriction on definition as (!), i.e. they must be 
defined in function style, not as an operator.


The change to the syntax would be to remove @ and ~ from the reserved 
operators list [2],

  reservedop - .. | : | :: | = | \ | | | - | - | @ | ~ | =
making it
  reservedop - .. | : | :: | = | \ | | | - | - | =


Oh, and while we are at it, I think (:) should also be removed as a 
reservedop, there is no reason for it to be on that list.



Twan

[1] Bang Patterns, Haskell-prime wiki
http://hackage.haskell.org/trac/haskell-prime/wiki/BangPatterns

[2] Haskell 98 report, lexical structure, identifiers and operators
http://haskell.org/onlinereport/lexemes.html#sect2.4

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Consistency of reserved operators and bang patterns

2007-09-07 Thread Isaac Dupree

Twan van Laarhoven wrote:
The bang pattern proposal [1] still allows (!) to be used as an 
operator. I think there should be no difference in this regard between ! 
and ~, since they are used in exactly the same location.


In my opinion the best thing would be to allow (~) and (@) as operators. 
With the same restriction on definition as (!), i.e. they must be 
defined in function style, not as an operator.


The change to the syntax would be to remove @ and ~ from the reserved 
operators list [2],

  reservedop - .. | : | :: | = | \ | | | - | - | @ | ~ | =
making it
  reservedop - .. | : | :: | = | \ | | | - | - | =


I agree - it confused me in the past that I couldn't define (@) or (~) 
operators.  Bang-pattern syntax being active will still change the 
meaning of


x ! y = z

of course.

Oh, and while we are at it, I think (:) should also be removed as a 
reservedop, there is no reason for it to be on that list.


Backwards compatibility requires that it be implicitly imported from 
Prelude even in a module that does import Prelude ( ) (although Hugs 
is already broken in this regard).  And that makes it fairly useless as 
a non-reserved symbol.  If not for that issue, I agree.


Isaac
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Consistency of reserved operators and bang patterns

2007-09-07 Thread Isaac Dupree

Isaac Dupree wrote:

Twan van Laarhoven wrote:
Oh, and while we are at it, I think (:) should also be removed as a 
reservedop, there is no reason for it to be on that list.


Backwards compatibility requires that it be implicitly imported from 
Prelude even in a module that does import Prelude ( ) (although Hugs 
is already broken in this regard).


In particular, Haskell-98 bans

import Prelude ( (:) )

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


RE: Bang patterns, ~ patterns, and lazy let

2006-02-08 Thread Simon Peyton-Jones
I've updated the Wiki to add your strict proposal, but rather briefly.
If you want to add stuff, send it to me and I'll add it.

Meanwhile:

| And as a consequence, it is no longer possible to transform a pair of
| bindings into a binding of a pair. In Haskell 98,
| 
| p1 = e1
| p2 = e2
| 
| is always equivalent to
| 
| (~p1, ~p2) = (e1,e2)

In your strict proposal, I'm sure you hope that the above pair would be
equivalent to
(p1,p2) = (e1,e2)
which would be even nicer.

But sadly I don't think it is, because that'd change the strongly
connected component structure.  Somehow that smells wrong.

Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Bang patterns, ~ patterns, and lazy let

2006-02-08 Thread John Hughes

Simon Peyton-Jones wrote:


I've updated the Wiki to add your strict proposal, but rather briefly.
If you want to add stuff, send it to me and I'll add it.

Meanwhile:

| And as a consequence, it is no longer possible to transform a pair of
| bindings into a binding of a pair. In Haskell 98,
| 
| p1 = e1

| p2 = e2
| 
| is always equivalent to
| 
| (~p1, ~p2) = (e1,e2)


In your strict proposal, I'm sure you hope that the above pair would be
equivalent to
(p1,p2) = (e1,e2)
which would be even nicer.

But sadly I don't think it is, because that'd change the strongly
connected component structure.  Somehow that smells wrong.

Simon
 

What have you got in mind? ANY tupling of bindings may change the SCC 
structure, and hence the results of type inference--I'm taking that as 
read. But that still leaves the question of whether the dynamic 
semantics of the program is changed. Let's assume for the time being 
that all bindings carry a type signature--then the SCC structure is 
irrelevant, isn't it? Or am I missing something here? I'm under the 
impression that the *dynamic* semantics of


   p1 = e1
   p2 = e2

*would* be the same as (p1,p2) = (e1,e2) under my strict matching 
proposal. I don't see how the SCC structure can affect that.


John

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Bang patterns, ~ patterns, and lazy let

2006-02-07 Thread John Hughes


   From: Ross Paterson [EMAIL PROTECTED]
   John Hughes wrote:

I would urge that either we stick with the present design, or, if bang 
patterns are added (which a lot speaks for), that the language be 
simplified at the same time so that patterns are matched in the same way 
everywhere, and BOTH warts above are excised. Some existing code would 
break, but in return the language would become simpler and more expressive.
   


   Would top-level bindings of constructor patterns and !x be evaluated
   when the module was loaded (or at compile time)?


Yes. Nothing else makes sense, does it? If that's problematic (although 
I can't see why it would be), just forbid strict patterns at the top 
level of modules.


Load time rather than compile-time, I think--otherwise the compiled code 
for a module could depend on the *code* of modules it imports, not just 
on their interfaces, which would be harmful for separate compilation.


John

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Bang patterns, ~ patterns, and lazy let

2006-02-07 Thread John Hughes






  
From: Ben Rudiak-Gould [EMAIL PROTECTED]
Subject: Re: Bang patterns, ~ patterns, and lazy let


  It's also not that case that !x has the same 
meaning in both proposals, e.g.

 let { !x = y ; !y = const 'a' x } in x

means 'a' in the current proposal but _|_ in yours.
  

Aargh, you're right, it does mean _|_ in mine! That's not very nice.

But wait, I'm not sure about
 let { !x = const undefined y ; !y = const 'a' x } in y
  
desugars in the current proposal to
  
let { x = const undefined y ; y = const 'a' x } in x `seq` y `seq` y
  
which is _|_, but absent implicit ~,
  
let { x = const undefined y ; y = const 'a' x } in y
  
had better (and does) mean 'a'. 
Applying the rules on the wiki, the first step is to translate the
first _expression_ into a tuple binding, omitting the implicit ~:

 let (x,y) = (const undefined y, const 'a' x) in y

This desugars to

 let (x,y) = fix (\ ~(x,y)-(const undefined y, const 'a' x)) in y

which evaluates to 'a'. In other words, despite the ! on x, the current
proposal is not strict in x.

Maybe the intention was that !s on the lhs of let bindings should be
transferred to the corresponding patterns when a tuple pattern is
introduced? Let's try it: then the example desugars by pattern tupling
to

 let (!x, !y) = (const undefined y, const 'a' x) in y

Now we can introduce fix:

 let (!x, !y) = fix (\ ~(!x, !y) - (const undefined y, const 'a'
x)) in y

and finally case:

 case fix (\~(!x,!y) - (const undefined y, const 'a' x)) of
~(!x, !y) - y

and this is consistent with what you said above.

But if I return to your first example, and do the same thing, I get

 let !x = y; !y = const 'a' x in x

desugars by tupling to

 let (!x, !y) = (y, const 'a' x) in x

which desugars by fix and case introduction to

 case fix (\ ~(!x, !y) - (y, const 'a' x)) of ~(!x, !y) - x

The first approximation to the fixed point is _|_, so the second is
(_|_, 'a'). Now, when ~(!x,!y) is matched against (_|_,'a') then *both*
variables are bound to _|_ --- the effect of the ~ is just to delay
matching (!x,!y) until one of the variables is used, but as soon as y,
say, *is* used, then the match is performed and, of course, it loops.
Thus (_|_, 'a') is the fixed point. For the same reason, x and y are
both bound to _|_ in the body of the case, and so the entire _expression_
evaluates to _|_, not 'a' as you claimed.

Bottom line: I can't find a way to interpret the translation rules in
the Haskell report, modified as the Wiki page suggests, to produce the
results you expect in both cases.

But maybe the fault is in the translation rules in the Haskell report.
It was always rather tricky to explain a group of recursive bindings in
Haskell in terms of a single tuple binding, because Haskell tuples are
lifted. I see that you have a more direct understanding of what ! is
supposed to mean. Is it possible, I wonder, to give a direct
denotational semantics to a declaration group--say mapping environments
to environments--in which there is only one case for ! (its natural
semantics in patterns)? Such a semantics should have the property that

 let x1 = e1; x2 = e2 in e0 === let x1 = e1 in let x2 = e2 in e0

provided x1 does not occur in e2. Finding a simple and compositional
denotational semantics with these properties, and proving the law
above, would be a good way to show that ! patterns do NOT introduce
semantic warts---and would probably also suggest that the
semantics-by-translation used in the report is fundamentally flawed. We
did construct denotational semantics of fragments of Haskell as part of
the original design, and it had quite an impact on the result--I
recommend it as a way of debugging ideas!

John


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Bang patterns

2006-02-06 Thread Simon Peyton-Jones
Earlier on the Haskell' list, I proposed bang patterns as a way to make
it more convenient for Haskell programmers to make their programs
stricter.  E.g.
f (!x, y) = 

I've documented the proposal here

http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/BangPatter
ns

I've implemented it in GHC, so you can try it out.  Use
-fbang-patterns
to enable bang patterns.   If you use -fglasgow-exts you get
-fbang-patterns as well.  If you don't want that, use -fglasgow-exts
-fno-bang-patterns.

I'd be interested to hear your experiences.  (Committee members: do add
notes to the Wiki page giving pros and cons.)

Simon 
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Bang patterns

2006-02-06 Thread Ben Rudiak-Gould
Pursuant to a recent conversation with Simon, my previous post to this 
thread is now obsolete. So please ignore it, and see the updated wiki page 
instead.


-- Ben

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime