Haskell 98 Revised

Ian Lynagh igloo@earth.li
Sun, 4 Nov 2001 00:46:34 +0000


Hi Simon

> It's that time of the month.   I'm putting out the November release
> of the Revised Haskell 98 Report.  As ever, I earnestly seek your
> feedback.

In appendix B (syntax), B.3 (layout) says

  * A stream of tokens as specified by the lexical syntax in the Haskell
    report, with the following additional tokens:
      + If the first *token after a let, where, do, or of keyword is not {, it
        is preceded by {n} where n is the indentation of the *token.
      + If the first *token of a module is not { or module, then it is preceded
        by {n} where n is the indentation of the *token.
      + Where the start of a *token does not follow any complete *token on the
        same line, this *token is preceded by <n> where n is the indentation of
        the *token, provided that it is not, as a consequence of the first two
        rules, preceded by {n}.

I think the word "token" should be replaced with "lexeme" where I have
marked it with *.

I am also not clear what you mean by "complete token"?

Finally, ghci, hi and hugs seem to accept

> instance Fractional Int where

as a valid program, but the layout rule doesn't seem to specify how ot
handle this (and as the last token is a new line token some simple fixes
don't work).

If I have this module:

> module Foo where
> instance Fractional Int where
> foo = 5

then with ghci I can evaluate foo:

    Compiling Foo              ( QQW.lhs, interpreted )

    QQW.lhs:3:
        Warning: No explicit method nor default method for `fromRational'
                 In the instance declaration for `Fractional Int'
    Foo> foo
    5
    Foo>

hi lets me load it but complains when I try to evaluate it:

    Prelude> foo
    [Compiling...
    ====================================
            Error when renaming::
    Identifier foo used at 10:21 is not defined. (in overlap resolution)
    ...failed]
    Prelude> 

and hugs won't even let me load it:

    Reading file "QQW.lhs":
    ERROR QQW.lhs:4 - No member "foo" in class "Fractional"
    Prelude> 

As the report stands I don't think any implementation does the right
thing, but that they should fail due to not being able to offsideify the
module as n == m on the line defining foo so the { is neither explicitly
nor implicitly provided for the idecls.


Thanks
Ian