> Someone recently submitted a bug report to the Hugs list as follows:
>
> >class C a where
> >f :: a
> >f = undefined
> 
> is parsed by Hugs as
> 
> >class C a where{
> >f :: a
> >;f = undefined}
> 
> which is incorrect - according to the specification of the layout rule
> in the Haskell 98 report, it should be parsed as
> 
> >class C a where{
> >};f :: a
> >;f = undefined
> 
> Now, while I can see a vague rationale for the new condition that
> definition lists must be indented strictly greater than the current
> indentation, it seems to me that this change was not widely announced,
> not discussed, and breaks many programs.

The proposal was on the Haskell 98 web page for quite a while before it was
finalised, and several people commented on it.

> For instance, I often use the following styles:
> 
> >f a b c =
> >  defs x
> >  where
> >  x = ...

That's fine, the new layout rule doesn't change the parsing of this
definition.  Remember, the outer syntax level starts with the 'f', the inner
level with the 'x ='.

> >  case exp of
> >  Nothing  -> ...
> >  (Just a) -> ...

Same here.

> >  do
> >  a <- exp1
> >  b <- exp2

And here.

> all of which are now rejected, even though they seem reasonable enough
> to me.  The new rule is also visually inconsistent, because
> 
> >module M where
> >f :: a
> >f = undefined
> 
> and
> 
> >class M where
> >f :: a
> >f = undefined
> 
> are now parsed differently, despite their apparent similarity.

Nope :)

>  (For
> the curious, the module declaration has an indentation of 0, by virtue
> of being the first decl in the file, while the f has indentation 1.)

The module declaration is not covered by the layout rule, because there's no
enclosing context.  Layout processing starts with the first 'f', having not
seen a '{' after the 'where' keyword.  The indentation of the 'f' sets the
indentation level for this context, at column 1.  In the second example, the
enclosing context is (I assume) layout at level 1, so it seems entirely
reasonable that the definition of 'f' should belong to the outer context and
the body of the class declaration is therefore empty. 

Admittedly it's a little tricky to implement this stuff properly, but I
believe the next version of GHC does so.  Feel free to prove me wrong :)

The modification to the layout rule was really a clarification - the
original rule left some cases ambiguous, with the result that different
compilers behaved differently.  GHC used to flag an error if the inner
context was <= the outer context, whereas Hugs used to accept it (and still
does - that's why I submitted the bug report).

eg. in

                f x = x where
                g x = x

since empty where clauses are allowed, there are two possible parses here -
unless we require that nested indentation levels are strictly increasing.
                
Cheers,
        Simon


Reply via email to