[Haskell-cafe] breaking too long lines

Christian Maeder Christian.Maeder at dfki.de
Mon Apr 20 08:56:39 EDT 2009


Hi,

according the several style guides, lines shouldn't be too long
(longer than 78 characters).

http://www.cs.caltech.edu/courses/cs11/material/haskell/misc/haskell_style_guide.html
http://www.haskell.org/haskellwiki/Programming_guidelines

However, I miss hints how to break lines best. Therefore I make some
suggestions here and ask for comments.

If a "one-liner" does not fit on one line I break the line after "="
rather than breaking the following infix- or prefix-expression.
(I break in the same way after "->" or "<-" in case- or do- expressions)
(Some people move "=" to the next line, but I only suggest this for
proper infix operators, below.)

If a "do" or a short
"case ... of" or "let ... in" fits, I leave it at the end of the
previous line behind "=" ("->" or "<-").

A line should be broken after "do" or "of" (from "case") in order to
allow insertions without breaking the layout, provided there is
preceding text at all.

The following is fine, because there's no text before "do")
   c x =
     do y <-...
        z ...

But this is fine, too, if not better:
  c x = do
    y <- ...
    z ...

It's not necessary to put "do" (or "let") on a separate line (and care
about the indentation of that keyword):
   c x =
     do
        y <-...
        z ...

Because layout may easily break (if b is renamed) and the layout block
starts already too far to the right, this is really bad:
  c b x =
    unless b $ do y <- ...
                  z ...

In many cases a "do" can be moved to the end of the previous line:
  c b x = unless b $ do
    y <- ...
    z

What applies to "do" could be applied to "let" as well (and vice versa),
but:
  f x = let
    y = x + x
    z = y + y
    in z

does not look as nice as:
  f x =
    let y = x + x
        z = y + y
    in z

And also a "let" (without "in") within a "do" should not be broken after
"let".

A long infix-expression should be broken _before_ an infix symbol to
better indicate it's continuation:

   f ++ g
     ++ h

   f . g
     $ h x

(One should also put spaces around infix operators and should not put
unnecessary brackets around prefix applications.)

Surely a long prefix expression can be broken anywhere, but I try to
break expressions on the top-level and not within too deeply nested
sub-expressions:
   f arg1 arg2 arg3
     (longArg4 sa1 sa2
       sa3 sa4)
     arg5 arg6 arg7

After a line break (following "=", "do", "<-", or "->") I try to stay as
far to the left as layout permits (using 2 spaces as minimal indentation).

I don't care if "=", <-", or "->" of one block line up (which surely is
difficult for the top-level module block) and I may put parts of the rhs
below parts of the lhs:

  let longPattern = case bla of
        Nothing -> "don't know"
	Just b ->
          "a longer expression"
      vN = ...

The standard breaking of if-then-else (within "do") is:
  if ...
    then ...
    else ...

but I think the following variations are also fine:
  ... <- if ...
   then ...
   else ...

  if ... then ... else
    ...

By chance I rarely use guards and "where", therefore I give no examples
for those expressions.

Somewhat tricky I've found are 2 do-expressions connected by an
infix-operator within an outer do-expression:
  do c <- letter
     do d <- digit
        return [c, d]
      <|> do
        u <- char '_'
	return [c, u]

The line containing "<|> do" is critical to indentation. If "<|> do" is
moved (2 columns) to the left it'll be wrong (by chance c will not be in
scope). If "<|> do" is moved (3 columns) to the right it'll mean
something different, namely parsing and returning a letter and a digit
_or_ parsing a letter, a digit, and an underscore, but only return the
letter and the underscore.

In order to more clearly put the infix operator into the middle I've
tried to insert one more space:
  do c <- letter
     do  d <- digit
         return [c, d]
       <|> do
         u <- char '_'
	 return [c, u]

Also the indentation of data types is an issue, because I think, code
shouldn't be indented due to long (constructor) names. I've nothing
against long names, but one shouldn't try to put blocks to the right of
them:
  data TName =
      LongConstructorName
      { selector1 :: C1
      , ... }
    | LongSecondConstructor
      ....
      deriving ...

Cheers Christian



More information about the Haskell-Cafe mailing list