Negation
S. Doaitse Swierstra
doaitse at cs.uu.nl
Tue Feb 9 16:43:02 EST 2010
One we start discussing syntax again it might be a good occasion to
reformulate/make more precise a few points.
The following program is accepted by the Utrecht Haskell Compiler
(here we took great effort to follow the report closely ;-} instead of
spending our time on n+k patterns), but not by the GHC and Hugs.
module Main where
-- this is a (rather elaborate) definition of the number 1
one = let x=1 in x
-- this is a definition of the successor function using section notation
increment = ( one + )
-- but if we now unfold the definition of one we get a parser error in
GHC
increment' = ( let x=1 in x + )
The GHC and Hugs parsers are trying so hard to adhere to the meta rule
that bodies of let-expressions
extend as far as possible when needed in order to avoid ambiguity,
that they even apply that rule when there is no ambiguity;
here we have only a single possible parse, i.e. interpreting the
offending expression as ((let x = 1 in ) +).
Yes, Haskell is both a difficult language to parse and to describe
precisely.
Doaitse
On 8 feb 2010, at 17:18, Simon Peyton-Jones wrote:
> Folks
>
> Which of these definitions are correct Haskell?
>
> x1 = 4 + -5
> x2 = -4 + 5
> x3 = 4 - -5
> x4 = -4 - 5
> x5 = 4 * -5
> x6 = -4 * 5
>
> Ghc accepts x2, x4, x6 and rejects the others with a message like
> Foo.hs:4:7:
> Precedence parsing error
> cannot mix `+' [infixl 6] and prefix `-' [infixl 6] in the
> same infix expression
>
> Hugs accepts them all.
>
> I believe that the language specifies that all should be rejected. http://haskell.org/onlinereport/syntax-iso.html
>
>
> I think that Hugs is right here. After all, there is no ambiguity
> in any of these expressions. And an application-domain user found
> this behaviour very surprising.
>
> I'm inclined to start a Haskell Prime ticket to fix this language
> definition bug. But first, can anyone think of a reason *not* to
> allow all the above?
>
> Simon
>
>
> _______________________________________________
> Haskell-prime mailing list
> Haskell-prime at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-prime
More information about the Haskell-prime
mailing list