[Haskell] offside rule question

Frederik Eaton frederik at a5.repetae.net
Wed Jul 13 20:09:02 EDT 2005


Compiling the following module (with ghc) fails with error message
"parse error (possibly incorrect indentation)", pointing to the let
statement. The error goes away when I indent the lines marked "--*".

But I don't understand how what I've written could be ambiguous. If I
am inside a parenthesized expression, then I can't possibly start
another let-clause. The fact that the compiler won't acknowledge this
fact ends up causing a lot of my code to be squished up against the
right margin when it seems like it shouldn't have to be.

module Main where

main :: IO ()
main = do
    let a = (map (\x->
        x+1) --*
        [0..9]) --*
    print a
    return ()

Is there a reason for this behavior or is it just a shortcoming of the
compiler?

Frederik


More information about the Haskell mailing list