RE: incorrect parsing

2002-01-04 Thread Simon Marlow

 On Thu, Jan 03, 2002 at 05:27:43PM -, Simon Marlow wrote:
  
  '(' exp(i+1) op(a,i) ')'
  '(' op(a,i) exp(i+1) ')'
  
  '(' 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.
 
 (+ 5) would not then be valid.

Oops, quite right.  Then we should follow the example of the lexp/rexp
productions:

'(' (lexp(i) | exp(i+1)) op(l,i) ')'
'(' op(r,i) (rexp(i) | exp(i+1)) ')'
'(' op(n,i) exp(i+1) ')'
'(' exp(i+1) op(n,i) ')'

Yeuch.  The grammar would be much more readable (not to mention
parseable) if fixity resolution was described seperately.

Cheers,
Simon

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



Re: incorrect parsing

2002-01-04 Thread Marcin 'Qrczak' Kowalczyk

Thu, 3 Jan 2002 17:27:43 -, Simon Marlow [EMAIL PROTECTED] pisze:

 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.

I would even argue that (a++b++) should mean \x - a++b++x
Of course Haskell 98 doesn't work this way.

-- 
 __(  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^
QRCZAK


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



Re: incorrect parsing

2002-01-03 Thread Ian Lynagh

On Thu, Jan 03, 2002 at 05:10:56PM +, 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



RE: incorrect parsing

2002-01-03 Thread Simon Marlow


 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