
http://www.haskell.org/~simonmar/haskell-2010-draft-report-2/haskellch10.htm... "Fixity resolution also applies to Haskell patterns, but patterns are a subset of expressions so in what follows we consider only expressions for simplicity." The string "1 * - 1" is legal as pattern, but rejected as expression! Furthermore fixity resolution does not distinguish between constructors and other operators as it should according to the grammar: pat → lpat qconop pat (infix constructor) | lpat funlhs → var apat { apat } | pat varop pat | ( funlhs ) apat { apat } "a : b * c : d = undefined" is currently rejected with: "cannot mix `:' [infixr 5] and `Main.*' [infixl 9] in the same infix expression" but should be fine by the given grammar (rule "pat varop pat"). Cheers Christian P.S. like in my proposal for infixexp I would change pat to: pat → pat qconop pat (infix constructor) | lpat for the sake of a better presentation only.

Christian Maeder schrieb:
http://www.haskell.org/~simonmar/haskell-2010-draft-report-2/haskellch10.htm...
"Fixity resolution also applies to Haskell patterns, but patterns are a subset of expressions so in what follows we consider only expressions for simplicity."
I suggest to change "also applies to Haskell patterns" to "also applies to Haskell patterns and left hand sides of infix function bindings"
The string "1 * - 1" is legal as pattern, but rejected as expression!
Further points: 1. "- 1 * 1" is accepted as legal pattern, but differently resolved for expressions! Should one not reject these (rare) patterns, too? 2. I would rather allow "1 * - 1" and "1 + - 1" to be legal as expressions (with its unambiguous interpretation). 3. Associativity should not matter for the non-binary "-"! So the following resolutions are possible: "1 + - 2 + 3" ~~~> "(1 + -2) + 3" "1 + - 2 * 3" ~~~> "1 + -(2 * 3)" infix 6 ## -- same precedence like "+" but different associativity "- 1 ## 2" ~~~> "(-1) ## 2" An infix-expression following an unary minus is resolved independently first. If the top-level operator has a strictly higher precedence than "-" its resolved as minus term, otherwise the same procedure is applied to the left argument of the infix expression. (If the left argument is no infix expression, we are done by plain prefix application of minus.)
Furthermore fixity resolution does not distinguish between constructors and other operators as it should according to the grammar:
pat → lpat qconop pat (infix constructor) | lpat
funlhs → var apat { apat } | pat varop pat
add a description: | pat varop pat (infix binding)
| ( funlhs ) apat { apat }
"a : b * c : d = undefined" is currently rejected with:
A similar example is given in 4.4.3.1 Function bindings. It should be referenced in 10.6 Fixity Resolution Cheers Christian
"cannot mix `:' [infixr 5] and `Main.*' [infixl 9] in the same infix expression"
but should be fine by the given grammar (rule "pat varop pat").
Cheers Christian
P.S. like in my proposal for infixexp I would change pat to:
pat → pat qconop pat (infix constructor) | lpat
for the sake of a better presentation only.

On 07/07/2010 10:09, Christian Maeder wrote:
Christian Maeder schrieb:
http://www.haskell.org/~simonmar/haskell-2010-draft-report-2/haskellch10.htm...
"Fixity resolution also applies to Haskell patterns, but patterns are a subset of expressions so in what follows we consider only expressions for simplicity."
I suggest to change "also applies to Haskell patterns" to
"also applies to Haskell patterns and left hand sides of infix function bindings"
The string "1 * - 1" is legal as pattern, but rejected as expression!
Further points:
1. "- 1 * 1" is accepted as legal pattern, but differently resolved for expressions! Should one not reject these (rare) patterns, too?
That's the GHC bug, right?
2. I would rather allow "1 * - 1" and "1 + - 1" to be legal as expressions (with its unambiguous interpretation).
Yes, me too, but that's a matter for a new proposal.
3. Associativity should not matter for the non-binary "-"!
So the following resolutions are possible:
"1 + - 2 + 3" ~~~> "(1 + -2) + 3" "1 + - 2 * 3" ~~~> "1 + -(2 * 3)"
infix 6 ## -- same precedence like "+" but different associativity
"- 1 ## 2" ~~~> "(-1) ## 2"
Yes, again I agree. The current fixity resolution is more strict than it needs to be. The intention in Haskell 2010 was not to change the way fixity resolution worked, but rather to avoid the problems caused by having it as part of the grammar. If you make a proposal to change this, then I would probably support it. Cheers, Simon
An infix-expression following an unary minus is resolved independently first. If the top-level operator has a strictly higher precedence than "-" its resolved as minus term, otherwise the same procedure is applied to the left argument of the infix expression. (If the left argument is no infix expression, we are done by plain prefix application of minus.)
Furthermore fixity resolution does not distinguish between constructors and other operators as it should according to the grammar:
pat → lpat qconop pat (infix constructor) | lpat
funlhs → var apat { apat } | pat varop pat
add a description: | pat varop pat (infix binding)
| ( funlhs ) apat { apat }
"a : b * c : d = undefined" is currently rejected with:
A similar example is given in 4.4.3.1 Function bindings. It should be referenced in 10.6 Fixity Resolution
Cheers Christian
"cannot mix `:' [infixr 5] and `Main.*' [infixl 9] in the same infix expression"
but should be fine by the given grammar (rule "pat varop pat").
Cheers Christian
P.S. like in my proposal for infixexp I would change pat to:
pat → pat qconop pat (infix constructor) | lpat
for the sake of a better presentation only.
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

Simon Marlow schrieb: [...]
1. "- 1 * 1" is accepted as legal pattern, but differently resolved for expressions! Should one not reject these (rare) patterns, too?
That's the GHC bug, right?
Yes!
2. I would rather allow "1 * - 1" and "1 + - 1" to be legal as expressions (with its unambiguous interpretation).
Yes, me too, but that's a matter for a new proposal.
3. Associativity should not matter for the non-binary "-"!
So the following resolutions are possible:
"1 + - 2 + 3" ~~~> "(1 + -2) + 3" "1 + - 2 * 3" ~~~> "1 + -(2 * 3)"
infix 6 ## -- same precedence like "+" but different associativity
"- 1 ## 2" ~~~> "(-1) ## 2"
Yes, again I agree. The current fixity resolution is more strict than it needs to be. The intention in Haskell 2010 was not to change the way fixity resolution worked, but rather to avoid the problems caused by having it as part of the grammar.
The grammar (in particular an ambiguous one) describes a superset of the language and need not change with a changed fixity resolution (or type analysis).
If you make a proposal to change this, then I would probably support it.
A larger case would be "1 * - 2 * 3", that I would resolve to "1 * - (2 * 3)" by resolving everything after "-" first. This is sort of an arbitrary choice, but probably ok and in the same spirit than resolving "- 2 * 3" to "- (2 * 3)". C.

On 07/07/2010 18:03, Christian Maeder wrote:
Simon Marlow schrieb: [...]
1. "- 1 * 1" is accepted as legal pattern, but differently resolved for expressions! Should one not reject these (rare) patterns, too?
That's the GHC bug, right?
Yes!
Just a meta point, but it would help me a great deal if you could clearly separate discussion of what GHC does from discussion of the standard, i.e. by using the different mailing lists.
2. I would rather allow "1 * - 1" and "1 + - 1" to be legal as expressions (with its unambiguous interpretation).
Yes, me too, but that's a matter for a new proposal.
3. Associativity should not matter for the non-binary "-"!
So the following resolutions are possible:
"1 + - 2 + 3" ~~~> "(1 + -2) + 3" "1 + - 2 * 3" ~~~> "1 + -(2 * 3)"
infix 6 ## -- same precedence like "+" but different associativity
"- 1 ## 2" ~~~> "(-1) ## 2"
Yes, again I agree. The current fixity resolution is more strict than it needs to be. The intention in Haskell 2010 was not to change the way fixity resolution worked, but rather to avoid the problems caused by having it as part of the grammar.
The grammar (in particular an ambiguous one) describes a superset of the language and need not change with a changed fixity resolution (or type analysis).
Please make a proposal (or proposals), then we can discuss exactly the changes you'd like to make. Cheers, Simon

Hi Simon and other fixity resolution friends, Fixity resolution starts from a sequence of expressions (lexp) interspersed by operator symbols, where some expressions may be preceded by unary minus signs. Between an operator and a following unary minus sign must be white space for the haskell lexer (as in "x == -1"). A binary minus is recognized (by the lexer), because it _follows_ an expression (lexp) unlike an unary minus (that precedes). Conceptually fixity resolution can be divided into two steps: 1. resolve prefix applications of unary minus 2. resolve infix applications There's no doubt how to resolve mere infix applications using precedences and associativity (2. step): A term a `o` b `p` c is uniquely resolve as: 2.a) (a `o` b) `p` c if prec(o) > prec(p) or prec(o) = prec(p) and both operator are left associative 2.b) a `o` (b `p` c) if prec(p) > prec(o) or prec(o) = prec(p) and both operator are right associative 2.c) unresolved otherwise The prefix applications of unary minus is a bit unusual (compared to other prefix applications) in that it binds weaker than multiplication: "- 1 * 2" is to be resolved as "- (1 * 2)" This weak binding is irrelevant for multiplication but essential for exponentiation, ie. "-x^2", and can make a difference for user defined infix operators, that bind strongest by default! Resolution of prefix "-" (1. step) works as follows: Unary minus applications extend as far to the right as _infix_ operators (no unary minus) have higher precedence than "+" or "-". A term like "- a * b ^ c < - d ^ e * f" is resolved as "- (a * b ^ c) < - (d ^ e * f)" or with more parens as "(- (a * b ^ c)) < (- (d ^ e * f))" which further resolves by infix resolution (2. step) to "(- (a * (b ^ c))) < (- ((d ^ e) * f))" In fact, this should finish fixity resolution, but the current haskell state unnecessarily restricts resolution further: 3.a) "a * - b" is rejected, because "*" binds stronger than "-" 3.b) "a + - b" is rejected, because "+" and "-" are not both right associative although both terms can be uniquely resolved to "a * (- b)" "a + (- b)". In other words, the operator to the left of an unary minus can be completely ignored for prefix minus resolution, simply because prefix minus does not have a left argument (like the binary minus)! Without this restriction polynomials like "- a + - b * x + - c * - x ^ 2" would uniquely resolve to "((- a) + (- (b * x))) + (- (c * (- (x ^ 2))))" I think hugs handles this correctly! Let us assume a user-defined (non- or) right-associative operator "#" with the same precedence as "+" and "-" (infix[r] 6 #). 3.c) both "- a # b" and "a # - b" are rejected, because "#" is not left-associative (like "-"). This unnecessary restriction rules out a (user-defined) polynomial like "- a # - b * x" for two reason (namely the two unary minus signs). Because an operator like "#" is not predefined, this restriction does not hurt as much as it does for "+" (and binary "-"). The unrestricted fixity resolution (1. and 2. step only, without restrictions 3.) can be further extended to allow multiple unary minus prefix applications. infixexp -> {-} lexp { op {-} lexp } White space is needed between "-" signs for lexing. Extended cases of 3.a) and 3.b) would be legal: "a * - - b" resolves uniquely to "a * (- (- b))" "a + - - b" resolves uniquely to "a + (- (- b))" It is, however, worth to remark that two consecutive unary "-" sign cannot be simply omitted: "a * - - b * c" resolves to "a * (- (- (b * c)))" whereas "a * b * c" resolves to "(a * b) * c" Even if double negation is the identity the grouping of factors has changed. An (alternative) implementation of the unrestricted fixity resolution can be found at: http://hackage.haskell.org/trac/ghc/ticket/4180 In comparison to the current restricted version the guard that checks the left operator before the unary minus can be omitted. Also giving the unary minus the same precedence and associativity than the binary minus makes the algorithm more restrictive. The unary minus needs a higher precedence than the binary "-" and a lower one than "*" or "/": Using http://darcs.haskell.org/haskell-prime it is enough to change: -type Prec = Int +type Prec = Float - = do guard (prec1 < 6) - (r, rest') <- parseNeg (Op "-" 6 Leftfix) rest + = do + (r, rest') <- parseNeg (Op "-" 6.5 Leftfix) rest Cheers Christian Relevant literature is: @Article{Aasa95, author = "Annika Aasa", title = "Precedences in Specifications and Implementations of Programming Languages", journal = "Theoret.\ Comput.\ Sci.", year = "1995", volume = "142", pages = "3--26", }

Christian Maeder schrieb: [...]
Without this restriction polynomials like "- a + - b * x + - c * - x ^ 2" would uniquely resolve to "((- a) + (- (b * x))) + (- (c * (- (x ^ 2))))"
I think hugs handles this correctly!
yes it does this case.
Let us assume a user-defined (non- or) right-associative operator "#" with the same precedence as "+" and "-" (infix[r] 6 #).
3.c) both "- a # b" and "a # - b" are rejected, because "#" is not left-associative (like "-").
hugs rejects only the case "- a # b": ERROR - Ambiguous use of unary minus with "(#)" So hugs still considers associativity for "-" (but does not consider the operator to the left of an unary minus.) C.
This unnecessary restriction rules out a (user-defined) polynomial like "- a # - b * x"

BTW, here's a related proposal made by Simon PJ earlier this year: http://hackage.haskell.org/trac/haskell-prime/wiki/NegationBindsTightly please consider merging the proposals, or at least clearly identifying the differences, if any. Cheers, Simon On 12/07/2010 08:40, Christian Maeder wrote:
Hi Simon and other fixity resolution friends,
Fixity resolution starts from a sequence of expressions (lexp) interspersed by operator symbols, where some expressions may be preceded by unary minus signs.
Between an operator and a following unary minus sign must be white space for the haskell lexer (as in "x == -1").
A binary minus is recognized (by the lexer), because it _follows_ an expression (lexp) unlike an unary minus (that precedes).
Conceptually fixity resolution can be divided into two steps:
1. resolve prefix applications of unary minus 2. resolve infix applications
There's no doubt how to resolve mere infix applications using precedences and associativity (2. step):
A term a `o` b `p` c is uniquely resolve as: 2.a) (a `o` b) `p` c if prec(o)> prec(p) or prec(o) = prec(p) and both operator are left associative 2.b) a `o` (b `p` c) if prec(p)> prec(o) or prec(o) = prec(p) and both operator are right associative 2.c) unresolved otherwise
The prefix applications of unary minus is a bit unusual (compared to other prefix applications) in that it binds weaker than multiplication:
"- 1 * 2" is to be resolved as "- (1 * 2)"
This weak binding is irrelevant for multiplication but essential for exponentiation, ie. "-x^2", and can make a difference for user defined infix operators, that bind strongest by default!
Resolution of prefix "-" (1. step) works as follows:
Unary minus applications extend as far to the right as _infix_ operators (no unary minus) have higher precedence than "+" or "-".
A term like "- a * b ^ c< - d ^ e * f" is resolved as "- (a * b ^ c)< - (d ^ e * f)" or with more parens as "(- (a * b ^ c))< (- (d ^ e * f))" which further resolves by infix resolution (2. step) to "(- (a * (b ^ c)))< (- ((d ^ e) * f))"
In fact, this should finish fixity resolution, but the current haskell state unnecessarily restricts resolution further:
3.a) "a * - b" is rejected, because "*" binds stronger than "-" 3.b) "a + - b" is rejected, because "+" and "-" are not both right associative
although both terms can be uniquely resolved to "a * (- b)" "a + (- b)".
In other words, the operator to the left of an unary minus can be completely ignored for prefix minus resolution, simply because prefix minus does not have a left argument (like the binary minus)!
Without this restriction polynomials like "- a + - b * x + - c * - x ^ 2" would uniquely resolve to "((- a) + (- (b * x))) + (- (c * (- (x ^ 2))))"
I think hugs handles this correctly!
Let us assume a user-defined (non- or) right-associative operator "#" with the same precedence as "+" and "-" (infix[r] 6 #).
3.c) both "- a # b" and "a # - b" are rejected, because "#" is not left-associative (like "-").
This unnecessary restriction rules out a (user-defined) polynomial like "- a # - b * x" for two reason (namely the two unary minus signs).
Because an operator like "#" is not predefined, this restriction does not hurt as much as it does for "+" (and binary "-").
The unrestricted fixity resolution (1. and 2. step only, without restrictions 3.) can be further extended to allow multiple unary minus prefix applications.
infixexp -> {-} lexp { op {-} lexp }
White space is needed between "-" signs for lexing. Extended cases of 3.a) and 3.b) would be legal: "a * - - b" resolves uniquely to "a * (- (- b))" "a + - - b" resolves uniquely to "a + (- (- b))"
It is, however, worth to remark that two consecutive unary "-" sign cannot be simply omitted: "a * - - b * c" resolves to "a * (- (- (b * c)))" whereas "a * b * c" resolves to "(a * b) * c"
Even if double negation is the identity the grouping of factors has changed.
An (alternative) implementation of the unrestricted fixity resolution can be found at: http://hackage.haskell.org/trac/ghc/ticket/4180
In comparison to the current restricted version the guard that checks the left operator before the unary minus can be omitted. Also giving the unary minus the same precedence and associativity than the binary minus makes the algorithm more restrictive. The unary minus needs a higher precedence than the binary "-" and a lower one than "*" or "/":
Using http://darcs.haskell.org/haskell-prime it is enough to change:
-type Prec = Int +type Prec = Float
- = do guard (prec1< 6) - (r, rest')<- parseNeg (Op "-" 6 Leftfix) rest + = do + (r, rest')<- parseNeg (Op "-" 6.5 Leftfix) rest
Cheers Christian
Relevant literature is:
@Article{Aasa95, author = "Annika Aasa", title = "Precedences in Specifications and Implementations of Programming Languages", journal = "Theoret.\ Comput.\ Sci.", year = "1995", volume = "142", pages = "3--26", }

Simon Marlow schrieb:
BTW, here's a related proposal made by Simon PJ earlier this year:
http://hackage.haskell.org/trac/haskell-prime/wiki/NegationBindsTightly
please consider merging the proposals, or at least clearly identifying the differences, if any.
Thanks for pointing this out. The difference lies in: - 1 ^ 2 which is currently (and by my proposal) resolved to "- (1 ^ 2)" whereas it would be resolved to "(-1) ^ 2" if negation binds tightly. Christian
Cheers, Simon
On 12/07/2010 08:40, Christian Maeder wrote:
Hi Simon and other fixity resolution friends,
Fixity resolution starts from a sequence of expressions (lexp) interspersed by operator symbols, where some expressions may be preceded by unary minus signs.
Between an operator and a following unary minus sign must be white space for the haskell lexer (as in "x == -1").
A binary minus is recognized (by the lexer), because it _follows_ an expression (lexp) unlike an unary minus (that precedes).
Conceptually fixity resolution can be divided into two steps:
1. resolve prefix applications of unary minus 2. resolve infix applications
There's no doubt how to resolve mere infix applications using precedences and associativity (2. step):
A term a `o` b `p` c is uniquely resolve as: 2.a) (a `o` b) `p` c if prec(o)> prec(p) or prec(o) = prec(p) and both operator are left associative 2.b) a `o` (b `p` c) if prec(p)> prec(o) or prec(o) = prec(p) and both operator are right associative 2.c) unresolved otherwise
The prefix applications of unary minus is a bit unusual (compared to other prefix applications) in that it binds weaker than multiplication:
"- 1 * 2" is to be resolved as "- (1 * 2)"
This weak binding is irrelevant for multiplication but essential for exponentiation, ie. "-x^2", and can make a difference for user defined infix operators, that bind strongest by default!
Resolution of prefix "-" (1. step) works as follows:
Unary minus applications extend as far to the right as _infix_ operators (no unary minus) have higher precedence than "+" or "-".
A term like "- a * b ^ c< - d ^ e * f" is resolved as "- (a * b ^ c)< - (d ^ e * f)" or with more parens as "(- (a * b ^ c))< (- (d ^ e * f))" which further resolves by infix resolution (2. step) to "(- (a * (b ^ c)))< (- ((d ^ e) * f))"
In fact, this should finish fixity resolution, but the current haskell state unnecessarily restricts resolution further:
3.a) "a * - b" is rejected, because "*" binds stronger than "-" 3.b) "a + - b" is rejected, because "+" and "-" are not both right associative
although both terms can be uniquely resolved to "a * (- b)" "a + (- b)".
In other words, the operator to the left of an unary minus can be completely ignored for prefix minus resolution, simply because prefix minus does not have a left argument (like the binary minus)!
Without this restriction polynomials like "- a + - b * x + - c * - x ^ 2" would uniquely resolve to "((- a) + (- (b * x))) + (- (c * (- (x ^ 2))))"
I think hugs handles this correctly!
Let us assume a user-defined (non- or) right-associative operator "#" with the same precedence as "+" and "-" (infix[r] 6 #).
3.c) both "- a # b" and "a # - b" are rejected, because "#" is not left-associative (like "-").
This unnecessary restriction rules out a (user-defined) polynomial like "- a # - b * x" for two reason (namely the two unary minus signs).
Because an operator like "#" is not predefined, this restriction does not hurt as much as it does for "+" (and binary "-").
The unrestricted fixity resolution (1. and 2. step only, without restrictions 3.) can be further extended to allow multiple unary minus prefix applications.
infixexp -> {-} lexp { op {-} lexp }
White space is needed between "-" signs for lexing. Extended cases of 3.a) and 3.b) would be legal: "a * - - b" resolves uniquely to "a * (- (- b))" "a + - - b" resolves uniquely to "a + (- (- b))"
It is, however, worth to remark that two consecutive unary "-" sign cannot be simply omitted: "a * - - b * c" resolves to "a * (- (- (b * c)))" whereas "a * b * c" resolves to "(a * b) * c"
Even if double negation is the identity the grouping of factors has changed.
An (alternative) implementation of the unrestricted fixity resolution can be found at: http://hackage.haskell.org/trac/ghc/ticket/4180
In comparison to the current restricted version the guard that checks the left operator before the unary minus can be omitted. Also giving the unary minus the same precedence and associativity than the binary minus makes the algorithm more restrictive. The unary minus needs a higher precedence than the binary "-" and a lower one than "*" or "/":
Using http://darcs.haskell.org/haskell-prime it is enough to change:
-type Prec = Int +type Prec = Float
- = do guard (prec1< 6) - (r, rest')<- parseNeg (Op "-" 6 Leftfix) rest + = do + (r, rest')<- parseNeg (Op "-" 6.5 Leftfix) rest
Cheers Christian
Relevant literature is:
@Article{Aasa95, author = "Annika Aasa", title = "Precedences in Specifications and Implementations of Programming Languages", journal = "Theoret.\ Comput.\ Sci.", year = "1995", volume = "142", pages = "3--26", }

Hi, I'm asking for support of: http://hackage.haskell.org/trac/haskell-prime/wiki/PrefixMinusResolution Cheers Christian Simon Marlow schrieb:
BTW, here's a related proposal made by Simon PJ earlier this year:
http://hackage.haskell.org/trac/haskell-prime/wiki/NegationBindsTightly
please consider merging the proposals, or at least clearly identifying the differences, if any.

I'm asking for support of: http://hackage.haskell.org/trac/haskell-prime/wiki/PrefixMinusResolution
Just to note that nhc98 appears to fulfill the outcome of this resolution algorithm already, with the exception of example x7, which is parsed as -(4#5). However, nhc98 goes further and permits the declaration of arbitrary prefix operators, using the syntax prefix negate 6 - yes, in addition to infix 6 - I think the rationale is that the prefix symbol must map to a non- symbolic function name, because the same symbol may also refer to a function of a different type when used infix. The resolution of prefix/infix chains and sections is quite involved, but not enormous: see http://darcs.haskell.org/york-compiler98/Fixity.hs Regards, Malcolm

Malcolm Wallace schrieb:
I'm asking for support of: http://hackage.haskell.org/trac/haskell-prime/wiki/PrefixMinusResolution
Just to note that nhc98 appears to fulfill the outcome of this resolution algorithm already, with the exception of example x7, which is parsed as -(4#5).
Because it seems to (unnecessarily) check if the operator # is left-associative. I assume that for "infixr 6 #" the term "-4 # 5 # 6" is resolved as "-(4 # (5 # 6))" (like it would be for "^"). How can I try out nhc98? My old installation is broken and http://www.haskell.org/haskellwiki/Implementations#nhc98 refers to no implementation. Is Yhc the compiler I should try?
However, nhc98 goes further and permits the declaration of arbitrary prefix operators, using the syntax
prefix negate 6 -
yes, this is a nice extension.
yes, in addition to
infix 6 -
I think the rationale is that the prefix symbol must map to a non-symbolic function name, because the same symbol may also refer to a function of a different type when used infix.
Currently there is no haskell way to _define_ a prefix operator therefore prefix minus is bound to negate explicitly as above (nhc98) or implicitly built-in (ghc and hugs). Prefix- and Infix-usage can be distinguished by the lexer: - a ... -> prefix a - ... -> infix Furthermore, prefix minus can not be qualified (bug or feature?). Prelude.- only refers to the infix version and "Prelude.- 1" is rejected (by ghc and hugs). Cheers Christian

On Jul 13, 2010, at 6:38 PM, Christian Maeder wrote:
I'm asking for support of:
http://hackage.haskell.org/trac/haskell-prime/wiki/PrefixMinusResolution
The wording in The operator to the left of prefix -, if there is one, is ignored. is unfortunate. Said operator is not *ignored* in the sense that `a + - b` parses as `a - b`. It is just not considered for fixity resolution of the mentioned occurrence of prefix -. (It may be considered for fixity resolution in a different context.) I don't have strong opinions on the content of the proposal, especially whether I prefer NegationBindsTightly or PrefixMinusResolution. (With the above sentence in mind, a funnier - and more specific - name would have been NegationBindsRightly :) aside>). The `- x^2` case is a good argument in favour of your proposal, but I'd want to also consider which one is easier to explain to the user and easier to implement (but I am lacking the required knowledge). The discussion on "prefix operators" (currently on this list) may shed some light on simplicity. Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

Hi, I prefer the simplicity of http://hackage.haskell.org/trac/haskell-prime/wiki/NegationBindsTightly over the more involved proposal. I think we should take every opportunity to simplify matters instead of complicating them. Although each individual improvement (like this) seems harmless, beneficial, and easy to implement, it is the combination of such features which often has given me unexpected implementation headaches (e.g. interaction with operator sections, or layout rule). More complex means more implementation effort means fewer tools which can assist with Haskell syntax, e.g. editing environments will have a tougher job of parsing correctly, fewer implementers will implement it. I'd gladly pay the price of adding some parenthesis to force "- x ^ 2" to "- (x ^ 2)". This is also much more clearer, less dependent on context info (i.e. the fixity of other operators), thus understandable without inspecting the definition of ^ in some other module, and thus also easier to explain (to students), and thus lessening the steepness of Haskells learning curve somewhat. cheers, On 13 Jul, 2010, at 18:38 , Christian Maeder wrote:
Hi,
I'm asking for support of:
http://hackage.haskell.org/trac/haskell-prime/wiki/PrefixMinusResolution
Cheers Christian
Simon Marlow schrieb:
BTW, here's a related proposal made by Simon PJ earlier this year:
http://hackage.haskell.org/trac/haskell-prime/wiki/NegationBindsTightly
please consider merging the proposals, or at least clearly identifying the differences, if any.
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
- 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@cs.uu.nl ............ / |___\

Atze Dijkstra schrieb:
Hi,
I prefer the simplicity of http://hackage.haskell.org/trac/haskell-prime/wiki/NegationBindsTightly over the more involved proposal.
It's a simple design choice but hard to put into practice for compatibility reasons. It is an old design choice between fortran and C style (earlier taken for Haskell) http://www.obliquity.com/computer/fortran/operate.html
I'd gladly pay the price of adding some parenthesis to force "- x ^ 2" to "- (x ^ 2)".
fortran and python have infix power operators that bind more tightly than unary minus. The mathematical unusual silent interpretation of "- x ^ 2" as "(- x) ^ 2" is the problem (and not that I better should write "- (x ^ 2)"). Other languages i.e. C do not have a power operator! Does "- pow x 2" read better? Leave it to users to define "^" and "**" as they like? Cheers Christian This is also much more clearer, less dependent on context info (i.e. the fixity of other operators), thus understandable without inspecting the definition of ^ in some other module, and thus also easier to explain (to students), and thus lessening the steepness of Haskells learning curve somewhat.
cheers,
On 13 Jul, 2010, at 18:38 , Christian Maeder wrote:
Hi,
I'm asking for support of:
http://hackage.haskell.org/trac/haskell-prime/wiki/PrefixMinusResolution
Cheers Christian
Simon Marlow schrieb:
BTW, here's a related proposal made by Simon PJ earlier this year:
http://hackage.haskell.org/trac/haskell-prime/wiki/NegationBindsTightly
please consider merging the proposals, or at least clearly identifying the differences, if any.
Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
- 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@cs.uu.nl ............ / |___\

On 14 Jul, 2010, at 14:22 , Christian Maeder wrote:
Atze Dijkstra schrieb:
Hi,
I prefer the simplicity of http://hackage.haskell.org/trac/haskell-prime/wiki/NegationBindsTightly over the more involved proposal.
It's a simple design choice but hard to put into practice for compatibility reasons.
It would indeed mean that some programs break, but is that bad? The situation would be similar to the removal of N+K patterns (finding out how many programs are influenced by it, requiring time to phase out, options to turn on/off the feature, etc). Sometimes some cleanup is required to make place for new stuff or to keep things manageable/implementable. What I want(ed) to emphasize is a concern for the implementability of Haskell as a whole and some sanity checks when considering the addition of feature X: (1) can some idea not be expressed without X? In this case 'no' because proper use of parenthesis can express the programmers intention. (2) can X be explained (and understood) by a 1st year student (or any other language beginner)? In this case explaining would be more difficult because the student mentally has to perform the same algorithm as the compiler does for X. On top of that the fixity environment must be remembered by the programmer. Using parenthesis is simpler. Of course such a list can be larger, but this seems relevant here.
fortran and python have infix power operators that bind more tightly than unary minus. The mathematical unusual silent interpretation of "- x ^ 2" as "(- x) ^ 2" is the problem (and not that I better should write "- (x ^ 2)").
Other languages i.e. C do not have a power operator! Does "- pow x 2" read better? Leave it to users to define "^" and "**" as they like?
I like your proposal as it stands, it solves a problem, sure! But like other seemingly innocent and nice solutions it also introduces less evident problems in other areas: for the programmer (must know more), for the implementer (because complexity of the whole is (sort of) quadratic in the number of features). In particular for parsing expressions I believe no compiler fully correctly did implement the (previous, Haskell98) language definition, so from an implementers point of view I prefer to first simplify matters until its implementable. To make this more concrete, UHC currently implements http://hackage.haskell.org/trac/haskell-prime/wiki/NegationBindsTightly. Not so much as a choice by desire, but out of necessity when debugging the parser for a problem which turned out to be caused by an error in layout parsing triggered by allowing nested do-statements have the same indentation. Simplicity in another part of the language (related to '-') did help to isolate the problem. cheers,
Cheers Christian
This is also much more clearer, less dependent on context info (i.e. the fixity of other operators), thus understandable without inspecting the definition of ^ in some other module, and thus also easier to explain (to students), and thus lessening the steepness of Haskells learning curve somewhat.
cheers,
On 13 Jul, 2010, at 18:38 , Christian Maeder wrote:
Hi,
I'm asking for support of:
http://hackage.haskell.org/trac/haskell-prime/wiki/PrefixMinusResolution
Cheers Christian
Simon Marlow schrieb:
BTW, here's a related proposal made by Simon PJ earlier this year:
http://hackage.haskell.org/trac/haskell-prime/wiki/NegationBindsTightly
please consider merging the proposals, or at least clearly identifying the differences, if any.
Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
- 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@cs.uu.nl ............ / |___\
- 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@cs.uu.nl ............ / |___\

Hi Atze, I share your desire for simplicity. In fact, I think my proposal is simpler than the existing ones of hugs, ghc, nhc98 and the language descriptions (98, 2010), although it's basically a matter of tuning. Layout and the type system are far more involving and should not interfere with fixity resolution! Simon said somewhere that fixity resolution takes basically 12 lines of haskell code. (My algorithm has 40 but shorter ones.) Furthermore, fixity resolution is a nice subject for teaching in conjunction with expression evaluation. I added a remark to the end of http://hackage.haskell.org/trac/haskell-prime/wiki/PrefixMinusResolution about rejecting prefix minus applications that do not bind tightly. It would use the same resolution algorithm with one modified line. It says: reject "- 1 ^ 2" always without parens in order to avoid the too simple (wrong) resolution as "(- 1) ^ 2". C. Atze Dijkstra schrieb:
On 14 Jul, 2010, at 14:22 , Christian Maeder wrote:
Atze Dijkstra schrieb:
Hi,
I prefer the simplicity of http://hackage.haskell.org/trac/haskell-prime/wiki/NegationBindsTightly over the more involved proposal. It's a simple design choice but hard to put into practice for compatibility reasons.
It would indeed mean that some programs break, but is that bad? The situation would be similar to the removal of N+K patterns (finding out how many programs are influenced by it, requiring time to phase out, options to turn on/off the feature, etc). Sometimes some cleanup is required to make place for new stuff or to keep things manageable/implementable.
What I want(ed) to emphasize is a concern for the implementability of Haskell as a whole and some sanity checks when considering the addition of feature X:
(1) can some idea not be expressed without X? In this case 'no' because proper use of parenthesis can express the programmers intention.
(2) can X be explained (and understood) by a 1st year student (or any other language beginner)? In this case explaining would be more difficult because the student mentally has to perform the same algorithm as the compiler does for X. On top of that the fixity environment must be remembered by the programmer. Using parenthesis is simpler.
Of course such a list can be larger, but this seems relevant here.
fortran and python have infix power operators that bind more tightly than unary minus. The mathematical unusual silent interpretation of "- x ^ 2" as "(- x) ^ 2" is the problem (and not that I better should write "- (x ^ 2)").
Other languages i.e. C do not have a power operator! Does "- pow x 2" read better? Leave it to users to define "^" and "**" as they like?
I like your proposal as it stands, it solves a problem, sure! But like other seemingly innocent and nice solutions it also introduces less evident problems in other areas: for the programmer (must know more), for the implementer (because complexity of the whole is (sort of) quadratic in the number of features). In particular for parsing expressions I believe no compiler fully correctly did implement the (previous, Haskell98) language definition, so from an implementers point of view I prefer to first simplify matters until its implementable. To make this more concrete, UHC currently implements http://hackage.haskell.org/trac/haskell-prime/wiki/NegationBindsTightly. Not so much as a choice by desire, but out of necessity when debugging the parser for a problem which turned out to be caused by an error in layout parsing triggered by allowing nested do-statements have the same indentation. Simplicity in another part of the language (related to '-') did help to isolate the problem.
cheers,
Cheers Christian
This is also much more clearer, less dependent on context info (i.e. the fixity of other operators), thus understandable without inspecting the definition of ^ in some other module, and thus also easier to explain (to students), and thus lessening the steepness of Haskells learning curve somewhat.
cheers,
On 13 Jul, 2010, at 18:38 , Christian Maeder wrote:
Hi,
I'm asking for support of:
http://hackage.haskell.org/trac/haskell-prime/wiki/PrefixMinusResolution
Cheers Christian
Simon Marlow schrieb:
BTW, here's a related proposal made by Simon PJ earlier this year:
http://hackage.haskell.org/trac/haskell-prime/wiki/NegationBindsTightly
please consider merging the proposals, or at least clearly identifying the differences, if any.
Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
- 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@cs.uu.nl ............ / |___\
- 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@cs.uu.nl ............ / |___\

I'd just like to remark that I think the current behaviour is the
right thing to do with respect to -x^2. Negation is related to
addition and so should always bind more weakly than multiplicative
operations.
- Cale
On 2010-07-15, at 4:31, Christian Maeder
Hi Atze,
I share your desire for simplicity. In fact, I think my proposal is simpler than the existing ones of hugs, ghc, nhc98 and the language descriptions (98, 2010), although it's basically a matter of tuning.
Layout and the type system are far more involving and should not interfere with fixity resolution!
Simon said somewhere that fixity resolution takes basically 12 lines of haskell code. (My algorithm has 40 but shorter ones.)
Furthermore, fixity resolution is a nice subject for teaching in conjunction with expression evaluation.
I added a remark to the end of http://hackage.haskell.org/trac/haskell-prime/wiki/PrefixMinusResolution about rejecting prefix minus applications that do not bind tightly. It would use the same resolution algorithm with one modified line.
It says: reject "- 1 ^ 2" always without parens in order to avoid the too simple (wrong) resolution as "(- 1) ^ 2".
C.

On 06/07/2010 18:12, Christian Maeder wrote:
http://www.haskell.org/~simonmar/haskell-2010-draft-report-2/haskellch10.htm...
"Fixity resolution also applies to Haskell patterns, but patterns are a subset of expressions so in what follows we consider only expressions for simplicity."
The string "1 * - 1" is legal as pattern, but rejected as expression!
Well, it's not a pattern (* is a varop, not a conop), and it's an illegal funlhs (* has greater precedence than prefix -).
Furthermore fixity resolution does not distinguish between constructors and other operators as it should according to the grammar:
pat → lpat qconop pat (infix constructor) | lpat
funlhs → var apat { apat } | pat varop pat | ( funlhs ) apat { apat }
"a : b * c : d = undefined" is currently rejected with:
"cannot mix `:' [infixr 5] and `Main.*' [infixl 9] in the same infix expression"
but should be fine by the given grammar (rule "pat varop pat").
The grammar specifies a superset of the language; fixity resolution may reject something that is legal according to the grammar. That's the change we made in Haskell 2010: the grammar no longer attempts to describe the language precisely with respect to fixity resolution, for good reasons (http://hackage.haskell.org/trac/haskell-prime/wiki/FixityResolution). See section 4.4.3.1 Function bindings: " Note that fixity resolution applies to the infix variants of the function binding in the same way as for expressions (Section 10.6). Applying fixity resolution to the left side of the equals in a function binding must leave the varop being defined at the top level. For example, if we are defining a new operator ## with precedence 6, then this definition would be illegal: a ## b : xs = exp because : has precedence 5, so the left hand side resolves to (a ## x) : xs, and this cannot be a pattern binding because (a ## x) is not a valid pattern. " Perhaps this could be clearer, please do suggest improvements.
P.S. like in my proposal for infixexp I would change pat to:
pat → pat qconop pat (infix constructor) | lpat
is there any need to do that? The grammar is non-ambiguous right now. Cheers, Simon

Simon Marlow schrieb:
The string "1 * - 1" is legal as pattern, but rejected as expression!
Well, it's not a pattern (* is a varop, not a conop), and it's an illegal funlhs (* has greater precedence than prefix -).
it is legal as funlhs (ghc-6.12.3)! 1 * - 1 = 2 Main> 1 Main.* (-1) 2 see also: http://hackage.haskell.org/trac/ghc/ticket/4176 Christian
Furthermore fixity resolution does not distinguish between constructors and other operators as it should according to the grammar:
pat → lpat qconop pat (infix constructor) | lpat
funlhs → var apat { apat } | pat varop pat | ( funlhs ) apat { apat }
"a : b * c : d = undefined" is currently rejected with:
"cannot mix `:' [infixr 5] and `Main.*' [infixl 9] in the same infix expression"
but should be fine by the given grammar (rule "pat varop pat").
The grammar specifies a superset of the language; fixity resolution may reject something that is legal according to the grammar. That's the change we made in Haskell 2010: the grammar no longer attempts to describe the language precisely with respect to fixity resolution, for good reasons (http://hackage.haskell.org/trac/haskell-prime/wiki/FixityResolution).
See section 4.4.3.1 Function bindings:
" Note that fixity resolution applies to the infix variants of the function binding in the same way as for expressions (Section 10.6). Applying fixity resolution to the left side of the equals in a function binding must leave the varop being defined at the top level. For example, if we are defining a new operator ## with precedence 6, then this definition would be illegal: a ## b : xs = exp
because : has precedence 5, so the left hand side resolves to (a ## x) : xs, and this cannot be a pattern binding because (a ## x) is not a valid pattern. "
Perhaps this could be clearer, please do suggest improvements.
P.S. like in my proposal for infixexp I would change pat to:
pat → pat qconop pat (infix constructor) | lpat
is there any need to do that? The grammar is non-ambiguous right now.
Cheers, Simon

On 07/07/2010 15:56, Christian Maeder wrote:
Simon Marlow schrieb:
The string "1 * - 1" is legal as pattern, but rejected as expression!
Well, it's not a pattern (* is a varop, not a conop), and it's an illegal funlhs (* has greater precedence than prefix -).
it is legal as funlhs (ghc-6.12.3)!
1 * - 1 = 2
Main> 1 Main.* (-1) 2
Well, that's a bug in GHC, not the Haskell report :-)
Thanks for reporting it. Cheers, Simon
Christian
Furthermore fixity resolution does not distinguish between constructors and other operators as it should according to the grammar:
pat → lpat qconop pat (infix constructor) | lpat
funlhs → var apat { apat } | pat varop pat | ( funlhs ) apat { apat }
"a : b * c : d = undefined" is currently rejected with:
"cannot mix `:' [infixr 5] and `Main.*' [infixl 9] in the same infix expression"
but should be fine by the given grammar (rule "pat varop pat").
The grammar specifies a superset of the language; fixity resolution may reject something that is legal according to the grammar. That's the change we made in Haskell 2010: the grammar no longer attempts to describe the language precisely with respect to fixity resolution, for good reasons (http://hackage.haskell.org/trac/haskell-prime/wiki/FixityResolution).
See section 4.4.3.1 Function bindings:
" Note that fixity resolution applies to the infix variants of the function binding in the same way as for expressions (Section 10.6). Applying fixity resolution to the left side of the equals in a function binding must leave the varop being defined at the top level. For example, if we are defining a new operator ## with precedence 6, then this definition would be illegal: a ## b : xs = exp
because : has precedence 5, so the left hand side resolves to (a ## x) : xs, and this cannot be a pattern binding because (a ## x) is not a valid pattern. "
Perhaps this could be clearer, please do suggest improvements.
P.S. like in my proposal for infixexp I would change pat to:
pat → pat qconop pat (infix constructor) | lpat
is there any need to do that? The grammar is non-ambiguous right now.
Cheers, Simon
participants (6)
-
Atze Dijkstra
-
Cale Gibbard
-
Christian Maeder
-
Malcolm Wallace
-
Sebastian Fischer
-
Simon Marlow