> This program:
> 
>     module Main where
>     f = map (++"a"++"b")
>     g = map ("a"++"b"++)
>     main = do print (f ["x","y","z"])
>               print (g ["x","y","z"])
> 
> gives the following error messages with ghc (versions 4.08.2 
> and 5.02):
> 
>     plusplus.hs:3:
>         The operator `++' [infixr 5] of a section
>             must have lower precedence than the operand `++' 
> [infixr 5]
>             In the section: `(++ ("a" ++ "b"))'
> 
>     plusplus.hs:4:
>         The operator `++' [infixr 5] of a section
>             must have lower precedence than the operand `++' 
> [infixr 5]
>             In the section: `(("a" ++ "b") ++)'
> 
> I believe this is the wrong behaviour - the first (right) section is
> perfectly valid Haskell'98 because the operator is right associative.
> Hugs, hbc, and nhc98 all accept it.  Check also section 3.5 (p.17)
> of the Report.
> 
> The second (left) section is indeed incorrect, again because the
> operator is right associative.

The text of section 3.5 seems to disagree with the syntax.  The syntax
says that these sections are allowed:

        '(' exp(i+1) op(a,i) ')'
        '(' op(a,i) exp(i+1) ')'

Which looks like the rule that GHC is implementing: the precedence of
the operator must be strictly lower than that of the expression.

I think it would be better to change the syntax to match the text rather
than the other way around: clearly sections like (++a++b) are desirable.
If I understand the notation in the report correctly, I think adding
these two productions to aexp would do the trick:

        '(' lexp(i) op(l,i) ')'
        '(' op(r,i) rexp(i) ')'

And for the sake of fewer ambiguities, replace each op(a,i) with op(n,i)
in the existing two section productions.

Cheers,
        Simon

_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to