Re: List syntax (was: Re: help from the community?)

2007-02-06 Thread Douglas Philips
On 2007 Feb 5, at 6:13 AM, Ulf Norell wrote: How about instead writing ( expr , expr , expr , expr , expr ) The only extra work is when inserting an element at the beginning, but you have the same problem in your example. This a coding style issue. My point was that the syntax should not

Re: List syntax (was: Re: help from the community?)

2007-02-06 Thread Jeffrey Yasskin
On 2/5/07, Ulf Norell [EMAIL PROTECTED] wrote: On Feb 3, 2007, at 6:35 AM, Douglas Philips wrote: Well, if we're going to bring personal points of view in, it highly pisses me off that in a construct such as: ( expr , expr , expr , expr , expr , ) I have to be vigilant to

Re: List syntax (was: Re: help from the community?)

2007-02-05 Thread Ulf Norell
On Feb 3, 2007, at 6:35 AM, Douglas Philips wrote: Well, if we're going to bring personal points of view in, it highly pisses me off that in a construct such as: ( expr , expr , expr , expr , expr , ) I have to be vigilant to remove that trailing comma when it is in _no way_

Re[2]: List syntax (was: Re: help from the community?)

2007-02-03 Thread Bulat Ziganshin
Hello Brian, Saturday, February 3, 2007, 10:55:52 AM, you wrote: bracket_ (enter a) (exit a) (do b c)-- looks like LISP... this pattern is very typical in my programs and i use '$' before last

Re: List syntax (was: Re: help from the community?)

2007-02-03 Thread Douglas Philips
On 2007 Feb 3, at 2:55 AM, Brian Hulley indited: Of course, but when I said error I meant error with respect to the intentions of the programmer not syntax error detected by the compiler. The problem with your proposal is that if optional trailing commas were allowed, if *I* wrote:

Re: List syntax (was: Re: help from the community?)

2007-02-03 Thread Brian Hulley
Douglas Philips wrote: On 2007 Feb 3, at 2:55 AM, Brian Hulley indited: I know, I find the need to manually delete and insert commas extremely tedious as well. This is why I proposed: ... I like that. (I haven't done enough analysis on the layout part of the grammar to personally make sure it

Re: List syntax (was: Re: help from the community?)

2007-02-03 Thread Taral
On 2/3/07, Brian Hulley [EMAIL PROTECTED] wrote: Of course, but when I said error I meant error with respect to the intentions of the programmer not syntax error detected by the compiler. The problem with your proposal is that if optional trailing commas were allowed, if *I* wrote: (1,2,)

Re: help from the community?

2007-02-03 Thread John Meacham
On Mon, Jan 29, 2007 at 10:08:59AM +0100, Andres Loeh wrote: I didn't fully understand this requirement. If Haskell-prime gets rank-2 or rank-n types, then do we need to restrict constructors in this way? Ok, this really boils down to the question of whether we do rank-2 or rank-n

Re: help from the community?

2007-02-02 Thread Malcolm Wallace
Douglas Philips [EMAIL PROTECTED] wrote: .to fark around with that stoopid ass ... Pisses off users ... domineering compiler writer can feel smug 'bout 'mself. Feh. Feh^2. Hey, man, take a chill pill.

List syntax (was: Re: help from the community?)

2007-02-02 Thread Douglas Philips
On 2007 Feb 2, at 5:46 AM, Malcolm Wallace indited: Since yours is the first actual flame I can remember ever being posted to any Haskell list, I think this counts as the beginning of the end of civilisation as we know it. :-) At least, the beginning of the end of civilised discussion.

Re: List syntax (was: Re: help from the community?)

2007-02-02 Thread Malcolm Wallace
Douglas Philips [EMAIL PROTECTED] wrote: What would be the proper way to propose that: | ( exp1 , ... , expk ) (tuple, k=2) | [ exp1 , ... , expk ] (list, k=1) be amended to: | ( exp1 , ... , expk [ , ] ) (tuple, k=2) | [ exp1 , ... , expk [

Re: List syntax (was: Re: help from the community?)

2007-02-02 Thread Brian Hulley
Douglas Philips wrote: What would be the proper way to propose that: ( exp1 , ... , expk ) (tuple, k=2) [ exp1 , ... , expk ] (list, k=1) be amended to: ( exp1 , ... , expk [ , ] ) (tuple, k=2) [ exp1 , ... , expk [ , ] ] (list, k=1) I think a problem with the above proposal is that by

Re: List syntax (was: Re: help from the community?)

2007-02-02 Thread Atze Dijkstra
On 2 Feb, 2007, at 16:55 , Malcolm Wallace wrote: Douglas Philips [EMAIL PROTECTED] wrote: What would be the proper way to propose that: | ( exp1 , ... , expk ) (tuple, k=2) | [ exp1 , ... , expk ] (list, k=1) be amended to: | ( exp1 , ... , expk [ ,

Re: List syntax (was: Re: help from the community?)

2007-02-02 Thread Douglas Philips
On 2007 Feb 2, at 11:32 AM, Brian Hulley wrote: Douglas Philips wrote: What would be the proper way to propose that: ( exp1 , ... , expk ) (tuple, k=2) [ exp1 , ... , expk ] (list, k=1) be amended to: ( exp1 , ... , expk [ , ] ) (tuple, k=2) [ exp1 , ... , expk [ , ] ] (list, k=1) I think

Re: List syntax (was: Re: help from the community?)

2007-02-02 Thread Kirsten Chevalier
On 2/2/07, Douglas Philips [EMAIL PROTECTED] wrote: I assert that the trailing comma is a feature, not a programmer forgetting the last element, and that this is already explicitly allowed, as per the syntax fragments already quoted, repeated here for convenience: -- from:

Re: List syntax (was: Re: help from the community?)

2007-02-02 Thread Douglas Philips
On 2007 Feb 2, at 12:13 PM, Kirsten Chevalier inquired: On 2/2/07, Douglas Philips [EMAIL PROTECTED] wrote: I assert that the trailing comma is a feature, not a programmer forgetting the last element, and that this is already explicitly allowed, as per the syntax fragments already quoted,

Re: List syntax (was: Re: help from the community?)

2007-02-02 Thread Kirsten Chevalier
On 2/2/07, Douglas Philips [EMAIL PROTECTED] wrote: Hmmm...stated another way: I am proposing that the list and tuple syntax change to be consistent with the import and export syntax. The argument that a trailing comma means the programmer forgot the last item in a list / tuple is inconsistent

RE: List syntax (was: Re: help from the community?)

2007-02-02 Thread Sittampalam, Ganesh
On 2/2/07, Kirsten Chevalier [EMAIL PROTECTED] wrote: On the other hand, with constant lists and tuples, you're probably not going to frequently edit the same constant list value. Am I missing something? Sometimes people maintain static configuration items and the like in lists. I've

Re: List syntax (was: Re: help from the community?)

2007-02-02 Thread Neil Mitchell
Hi The argument that a trailing comma means the programmer forgot the last item in a list / tuple is inconsistent with the deliberately explicit permissiveness of a trailing comma in the import / export lists. In the import / export lists such a trailing comma does not mean programmer forgot

Re: List syntax (was: Re: help from the community?)

2007-02-02 Thread Douglas Philips
On 2007 Feb 2, at 1:03 PM, Neil Mitchell indited: The argument that a trailing comma means the programmer forgot the last item in a list / tuple is inconsistent with the deliberately explicit permissiveness of a trailing comma in the import / export lists. In the import / export lists such a

Re: List syntax (was: Re: help from the community?)

2007-02-02 Thread Kirsten Chevalier
On 2/2/07, Douglas Philips [EMAIL PROTECTED] wrote: On 2007 Feb 2, at 1:03 PM, Neil Mitchell indited: An import list is not a value, you can't examine whats in the list, you can't enumerate it etc. As such, it doesn't really matter how many elements are in there, the important thing is what

Re: List syntax (was: Re: help from the community?)

2007-02-02 Thread Brian Hulley
Douglas Philips wrote: On 2007 Feb 2, at 1:03 PM, Neil Mitchell indited: Personally I'd make the rule that trailing commas are never allowed, anywhere, but I do see an argument for adding them to import lists. You just highlighted the inconsistency: You refer to import lists... you appear to

Re: List syntax (was: Re: help from the community?)

2007-02-02 Thread Douglas Philips
On 2007 Feb 2, at 11:25 PM, Brian Hulley indited: Apart from the extra possibility for errors (yes I understood that you'd define it to not be an error but this doesn't change the fact that for people who always wrote their tuples using the normal mathematical convention not using an

Re: List syntax (was: Re: help from the community?)

2007-02-02 Thread Brian Hulley
Douglas Philips wrote: On 2007 Feb 2, at 11:25 PM, Brian Hulley indited: Apart from the extra possibility for errors (yes I understood that you'd define it to not be an error but this doesn't change the fact that for people who always wrote their tuples using the normal mathematical convention

Re: help from the community?

2007-02-01 Thread Brian Hulley
Taral wrote: On 1/31/07, Conor McBride [EMAIL PROTECTED] wrote: So, as far as Haskell' is concerned, I'd favour forbidding non-empty cases, but only because I favour having some more explicit syntax for empty cases, further down the line. I see nothing wrong with case x of {}, with required

Re: help from the community?

2007-02-01 Thread Stephanie Weirich
Here are some of my comments to Iavor's proposals: Notation for Schemes PROPOSAL: be liberal: allow empty quantifier lists allow variables that are not mentioned in the body of a type (but warn) allow predicates that do not mention quantified variables (but warn?) For the reasons

Re: help from the community?

2007-02-01 Thread Malcolm Wallace
On 1 Feb 2007, at 21:31, Jacques Carette wrote: Stephanie Weirich wrote: I don't think we want to allow types like: forall . Int or forall a b. Int These types are mostly bugs. Furthermore, rejecting them doesn't limit expressiveness: If you restrict yourself to programs

Re: help from the community?

2007-02-01 Thread Ashley Yakeley
Malcolm Wallace wrote: I find the program-generated code argument rather weak. One might satisfy both camps by having a compiler flag to allow auto-generated ugliness. -- Ashley Yakeley ___ Haskell-prime mailing list Haskell-prime@haskell.org

Re: help from the community?

2007-02-01 Thread Jacques Carette
Malcolm Wallace wrote: If you restrict yourself to programs entirely written by humans, I agree completely. But if you consider programs written by programs (say Template Haskell to be specific, but it could be via many other means), such degenerate types occur rather often. I find the

Re: help from the community?

2007-02-01 Thread Douglas Philips
On 2007 Feb 1, at 4:53 PM, Malcolm Wallace indited: I find the program-generated code argument rather weak. In that past it was used to justify all kinds of minor horrors like excess commas in lists and so on. ... That only encourages humans to use sloppy practices in hand-written code as

Re: help from the community?

2007-01-31 Thread Andres Loeh
Just a little remark on the side: 'If' and 'case' demand exactly one expression. In such cases allowing zero expressions is not a generalization but an unnecessary complication. 'Let' and 'where' allow any number of bindings, so allowing zero bindings (instead of demanding at least one) is a

Re: help from the community?

2007-01-31 Thread Conor McBride
Hi Andres Loeh wrote: I think it's important to keep some possibility for the compiler to detect probable errors as syntax errors. If all syntax is inhabited by strange defaults then this just means simple errors will go undetected eg: let a = case foo of Here, the user has probably got

Re: help from the community?

2007-01-31 Thread Taral
On 1/31/07, Conor McBride [EMAIL PROTECTED] wrote: So, as far as Haskell' is concerned, I'd favour forbidding non-empty cases, but only because I favour having some more explicit syntax for empty cases, further down the line. I see nothing wrong with case x of {}, with required braces. The

Re: help from the community?

2007-01-31 Thread Ashley Yakeley
Taral wrote: I see nothing wrong with case x of {}, with required braces. The layout rule never generates empty braces. Also consider a simple case x, following the already allowed omission of where in class and instance decls. class (This a,That a) = ThisThat a instance (This a,That

Re: help from the community?

2007-01-31 Thread Conor McBride
Hi Ashley Yakeley wrote: Taral wrote: I see nothing wrong with case x of {}, with required braces. The layout rule never generates empty braces. Also consider a simple case x, [..] This will be useful for GADTs: data MyGADT a where IntGADT :: MyGADT Int never :: MyGADT Char -

RE: help from the community?

2007-01-30 Thread Simon Peyton-Jones
| I can also imagine predicates that do not mention locally-quantified | variables - the assumption must be that they mention variables bound on | the LHS of the datatype decl instead? e.g. the Show predicate here: | | data Foo a b = Foo a b | | Bar (forall c . (Show b,

Re: help from the community?

2007-01-30 Thread Benjamin Franksen
Andres Loeh wrote: I cannot see how an empty list of tyvars is useful or desirable in practice: data Foo = Foo (forall . Int) is equivalent to just data Foo = Foo Int so why bother to permit the former? It probably indicates some error in the thinking of the programmer, so the

Re: help from the community?

2007-01-30 Thread Andres Loeh
The only reasons that I could see in favor of allowing empty foralls is that it might be easier to automatically generate code. Haskell seems to be a bit inconsistent in how it treats empty constructs. For example, empty let and empty where seems to be allowed, but not an empty case?

Re: help from the community?

2007-01-30 Thread Brian Hulley
Andres Loeh wrote: The only reasons that I could see in favor of allowing empty foralls is that it might be easier to automatically generate code. Haskell seems to be a bit inconsistent in how it treats empty constructs. For example, empty let and empty where seems to be allowed, but not an

Re: help from the community?

2007-01-29 Thread Andres Loeh
I cannot see how an empty list of tyvars is useful or desirable in practice: data Foo = Foo (forall . Int) is equivalent to just data Foo = Foo Int so why bother to permit the former? It probably indicates some error in the thinking of the programmer, so the compiler should bring

Re: help from the community?

2007-01-26 Thread Malcolm Wallace
isaac jones [EMAIL PROTECTED] wrote: http://hackage.haskell.org/trac/haskell-prime/ticket/57 Does anyone have any feedback on this work? Yes, here are my thoughts. PROPOSAL: adopt GHC's convention and treat 'forall' specially in types but allow it to be used in value declarations.