[Haskell-cafe] Code layout in Emacs' haskell-mode

Nick Meyer npmeyer at syr.edu
Mon May 14 12:05:25 EDT 2007


Hi Christopher,

I have also noticed that haskell-mode (and indeed Haskell) can be finicky
sometimes.  I usually put "module [Name] where" all on the same line and
leave "import"s on the left margin, so I hadn't experienced the first
problem you mentioned.  However, I do notice that if I re-arrange your
second example so that "do" and the first "putStrLn" are on the same line,
emacs offers the following indentation:

module Num where
import IO

main = do putStrLn "Enter a number: "
          inp <- getLine
          let n = read inp
          if n == 0
          then putStrLn "Zero"
          else putStrLn "NotZero"

(that's with all the expressions in the do block lining up vertically, if
that doesn't show up in a fixed-width font), it works!  I would think that
your original indentation gave an error in that GHC would see "then" and
"else" and assume they were new expressions, but then I would expect that
this would have the same problem.  If anyone can shed some light on this,
that would be nice.

Thanks,
Nick Meyer
npmeyer at syr.edu

On 5/14/07, Christopher L Conway <cconway at cs.nyu.edu> wrote:
> I am new to Haskell---and also to languages with the off-side
> rule--and working my way through Hal Daume's tutorial. I'm a little
> confused by the support for code layout in Emacs' haskell-mode. Is it
> buggy, or am I doing something wrong.
>
> For example, here's the "Hello, world" example from the tutorial, with
> the indentation induced by pounding Tab in haskell-mode.
>
> test.hs:
> module Test
>     where
>
>       import IO
>
> main = do
>   putStrLn "Hello, world"
>
> Prelude> :l test
> [1 of 1] Compiling Test             ( test.hs, interpreted )
>
> test.hs:12:0: parse error on input `main'
>
> In emacs, every line but the one with "where" reports "Sole
> indentation". With "where", I have the option of having it flush left
> or indented four spaces; "import" wants to be two spaces in from
> "where". Moving where doesn't change the error. But if I manually move
> import flush left (which is the way it's shown in the tutorial, BTW):
>
> module Test
>     where
>
> import IO
>
> main = do
>   putStrLn "Hello, world"
>
> Prelude> :l test
> [1 of 1] Compiling Test             ( test.hs, interpreted )
> Ok, modules loaded: Test.
>
> I have a similar problem with the layout of if-then-else...
>
> num.hs:
> module Num
>     where
>
> import IO
>
> main = do
>   putStrLn "Enter a number: "
>   inp <- getLine
>   let n = read inp
>   if n == 0
>   then putStrLn "Zero"
>   else putStrLn "NotZero"
>
> Prelude> :l num
> [1 of 1] Compiling Num              ( num.hs, interpreted )
>
> num.hs:11:2: parse error (possibly incorrect indentation)
>
> Again, if I hit tab on the "then" or "else" lines, emacs reports "Sole
> indentation". But if I manually change the indentation, it works.
>
> module Num
>     where
>
> import IO
>
> main = do
>   putStrLn "Enter a number: "
>   inp <- getLine
>   let n = read inp
>   if n == 0
>      then putStrLn "Zero"
>      else putStrLn "NotZero"
>
> Prelude> :l num
> [1 of 1] Compiling Num              ( num.hs, interpreted )
> Ok, modules loaded: Num.
>
> This is particularly weird because if-then-else doesn't always act this
way:
>
> exp.hs:
> module Exp
>     where
>
> my_exponent a n =
>     if n == 0
>     then 1
>     else a * my_exponent a (n-1)
>
> Prelude> :l exp
> [1 of 1] Compiling Exp              ( exp.hs, interpreted )
> Ok, modules loaded: Exp.
>
> I suppose this might have something to do with the do-notation...
>
> Does haskell-mode support code layout? Are there conventions I need to
> know about to make it behave properly? I have haskell-mode version
> 2.1-1 installed from the Ubuntu feisty repository.
>
> Thanks,
> Chris
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20070514/663e993d/attachment.htm


More information about the Haskell-Cafe mailing list