[EMAIL PROTECTED] (Carl R. Witty) wrote,

> "Manuel M. T. Chakravarty" <[EMAIL PROTECTED]> writes:
> 
> > One of our students just pointed out an IMHO rather
> > problematic clause in the layout rule.  In Section 2.7 of
> > the Haskell 98 Report it says,
> > 
> >   A close brace is also inserted whenever the syntactic
> >   category containing the layout list ends; that is, if an
> >   illegal lexeme is encountered at a point where a close
> >   brace would be legal, a close brace is inserted.
> > 
> > And in B.3, we have in the first equation of the definition
> > of `L',
> > 
> >   L (t:ts) (m:ms) = } : (L (t:ts) ms)   if parse-error(t)  (Note 1)
> > 
> > where Note 1 says,
> > 
> >   The side condition parse-error(t) is to be interpreted as
> >   follows: if the tokens generated so far by L together with
> >   the next token t represent an invalid prefix of the
> >   Haskell grammar, and the tokens generated so far by L
> >   followed by the token } represent a valid prefix of the
> >   Haskell grammar, then parse-error(t) is true.
> 
> Consider the following to see the true horror of the parse-error
> condition of the layout rule.  As far as I can tell (assuming the
> standard prelude), the phrase
>    do a == b == c
> is legal and parses as 
>    do {a == b} == c
> but
>    do a `elem` b `elem` c
> is a syntax error.  (Both == and `elem` are "infix 4".)
> 
> Since == is non-associative,
>    do { a == b ==
> is not a legal prefix of the Haskell grammar, and
>    do { a == b }
> is.  So the layout rule inserts the implicit close-brace before the
> second ==.
> 
> However,
>    do { a `elem` b `
> is a legal prefix of the Haskell grammar: it could be completed by
>    do { a `elem` b `seq` c }
> for instance.  So no implicit close-brace gets inserted; and
>    a `elem` b `elem` c
> is a syntax error.
> 
> Does anybody disagree with my interpretation of the
> standard?  

Seems plausible to me.

> Are there any implementations that actually follow the
> standard here?  

GHC (4.02) and Hugs 98 do not recognise

  do a == b == c

They produce an error messge complaining about the mismatch
of associativity.  

Manuel


Reply via email to