[Haskell] offside rule question

Lennart Augustsson lennart at augustsson.net
Wed Jul 13 20:42:53 EDT 2005


That's how it is defined in the Haskell definition.

But there is a reason.  The offside rule (or whatever yoy want to
call it) is there to give visual cues.  If you were allowed to override
these easily just because it's parsable in principle then your code
would no longer have these visual cues that make Haskell code fairly
easy to read.

	-- Lennart

Frederik Eaton wrote:
> 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
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
> 



More information about the Haskell mailing list