[Haskell-cafe] Layout rule (was Re: PrefixMap: code reviewrequest)

Daniel Fischer daniel.is.fischer at web.de
Sat Mar 4 05:34:48 EST 2006


Am Freitag, 3. März 2006 19:21 schrieb Brian Hulley:
> Brian Hulley wrote:
> > Brian Hulley wrote:
> > One other thing I've been wanting to ask (not to change! :-)) for a
> > while is: how is the following acceptable according to the rules in
> > the Haskell98 report where "where" is one of the lexemes, which when
> > followed by a line more indented than the line the
> > layout-starting-lexeme is on, should start an implicit block:
> >
> >       module M where
> >       data T = .....            -- not indented!
> >
> > According to my understanding of the layout algorithm, the above code
> > would have to be written:
> >
> >       module M where
> >              data T = ....
> >
> > Can anyone shed some light on what the formal rule is that allows the
> > first (and very useful) way of laying out code to be ok?
>
> The solution (as someone pointed out to me in an email) is that the layout
> block only *finishes* when the current indentation is *less* than the
> indentation of the lines in the layout block (rather than *starting* only
> when the current indentation is *more* than the indentation of the line
> containing the "where" etc).
>
> However I think there is an error in the description of this in section 2.7
> of the Haskell98 report, which states:
>
> "If the indentation of the non-brace lexeme immediately following a where,
> let, do or of is less than or equal to the current indentation level, then
> instead of starting a layout, an empty list "{}" is inserted, and layout
> processing occurs for the current level ..."
>
> I dispute the "or equal" in the above statement, since it seems to be
> clearly in contradiction to what is actually being done.
>
> Regards, Brian.
>

AFAICT, the description in the report is correct, *except for the 'where' in 
module LayOut where*.
Consider

module LayOut
where

fun x y = bum x y + y 4
          where

bum x y = y x

a) the module-where is at indentation level 0, accepted here, but nowhere 
else, even if I indent fun and bum, fun's where must be indented further than 
fun itself.

b) bum's definition is top-level now, but in
module LayOut
where

    fun x y = bum x y + y 4
        where

     bum x y = y x

it is local (bum is indented more than fun, but less than where), in perfect 
accord with the report.

Even
        module LayOut
 ( fun,
bum)
    where

    fun x y = bum x y + y 4
        where

    bum x y = y x

is accepted.
So my guess is that layout-processing is applied only to the module-body, not 
to the module head and probably that should be mentioned in the report.
BTW, when I read about layout in the report, this irritated me, too, so thanks 
for asking.

Cheers,
Daniel

-- 

"In My Egotistical Opinion, most people's C programs should be
indented six feet downward and covered with dirt."
	-- Blair P. Houghton



More information about the Haskell-Cafe mailing list