Layout indentation marking

Ian Lynagh igloo@earth.li
Sun, 10 Mar 2002 15:22:40 +0000


Given this module

    module Main where

    main :: IO()
    main = putStrLn $ show $ foo

    foo :: Int
    foo = x + y
      where x = 6
            s = "foo\
      \bar" y = 7

nhc98 and hugs correctly (as per the revised report) print 13. ghc gives

    q.lhs:11: parse error on input `='

I think ghc is in the right here and the report should be updated to
read

      + Where the start of a lexeme does not follow the end of a lexeme on
        the same line, this lexeme is preceded by <n> where n is the
        indentation of the lexeme, provided that it is not, as a
        consequence of the first two rules, preceded by {n}. (A string
        literal may span multiple lines -- Section 2.6.)

(it currently reads

      + Where the start of a lexeme does not follow a complete lexeme on
        the same line, this lexeme is preceded by <n> where n is the
        indentation of the lexeme, provided that it is not, as a
        consequence of the first two rules, preceded by {n}. (A string
        literal may span multiple lines -- Section 2.6.)

where I have altered only the first line).


Thanks
Ian