On Thu, Jan 03, 2002 at 05:10:56PM +0000, Malcolm Wallace wrote:
> 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"))'
> 
> 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 context free grammar in appendix B (and at the start of section 3)
defines right sections as
    ( qop(a,i) expi+1 )
which contradicts 3.5. The additional production to
    ( qop(r,i) rexpi )
could be added, and similarly for left sections.

The brackets added to the error would make the section valid anyway
which should perhaps be fixed regardless.


Thanks
Ian


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

Reply via email to