Re: [Haskell-cafe] Coding conventions for Haskell?

2010-10-03 Thread Henning Thielemann
Andrew Coppin schrieb:

  On 30/09/2010 02:56 PM, Henning Thielemann wrote:

 In Cabal you can write one module per line and need no separator or
 terminator at all.
 
 Really? As far as I can tell, that doesn't work at all...

See e.g.

http://hackage.haskell.org/packages/archive/utility-ht/0.0.5.1/utility-ht.cabal
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-10-01 Thread Andrew Coppin

 On 30/09/2010 02:56 PM, Henning Thielemann wrote:

Andrew Coppin schrieb:

  On 29/09/2010 02:18 PM, Henning Thielemann wrote:

The truth is: Given the separator style of constructor definition,
there is no correct way to format those declarations. :-) The correct
way would be to allow terminator style.

Well, yes, there is that. (And this isn't the only place in the syntax
where it applies either. Tried editing export lists lately? Or Cabal
module lists?)

In export and import lists you can use commas as terminators, however in
constructor lists you cannot.


I accidentally discovered that it works in export lists a few weeks ago. 
I assumed it was a bug.



In Cabal you can write one module per line and need no separator or
terminator at all.


Really? As far as I can tell, that doesn't work at all...

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-30 Thread Henning Thielemann
Andrew Coppin schrieb:
  On 29/09/2010 02:18 PM, Henning Thielemann wrote:

 The truth is: Given the separator style of constructor definition,
 there is no correct way to format those declarations. :-) The correct
 way would be to allow terminator style.
 
 Well, yes, there is that. (And this isn't the only place in the syntax
 where it applies either. Tried editing export lists lately? Or Cabal
 module lists?)

In export and import lists you can use commas as terminators, however in
constructor lists you cannot.

module A (a, b, c, T(A,B,C), ) where

import X (x, Y(M,N,O), z, )


In Cabal you can write one module per line and need no separator or
terminator at all.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-30 Thread Christopher Done
FWIW, I align all my module imports up, as seen here:
http://github.com/chrisdone/amelie/raw/master/src/Web/Codepad.hs  and
here http://github.com/chrisdone/amelie/raw/master/src/Amelie/HTML.hs
etc.

I use the following Emacs library to do it for me:
http://github.com/chrisdone/haskell-mode-exts/raw/master//haskell-align-imports.el

I also sort them with this:
http://github.com/chrisdone/haskell-mode-exts/blob/master//haskell-sort-imports.el
but it only works for one-line imports, which I advocate anyway.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-30 Thread Roel van Dijk
I align my imports by hand, but your Emacs scripts look useful. I
think I'm going to use them too.

Another extremely useful function for aligning is align-regexp.

On the subject of coding style, I can work with almost any style as
long as it is used somewhat consistently. Personally I try to optimize
my code for ease of reading because I spend much more time reading
code than writing. Aligning stuff vertically makes it easier to spot
differences.

On Thu, Sep 30, 2010 at 4:02 PM, Christopher Done
chrisd...@googlemail.com wrote:
 FWIW, I align all my module imports up, as seen here:
 http://github.com/chrisdone/amelie/raw/master/src/Web/Codepad.hs  and
 here http://github.com/chrisdone/amelie/raw/master/src/Amelie/HTML.hs
 etc.

 I use the following Emacs library to do it for me:
 http://github.com/chrisdone/haskell-mode-exts/raw/master//haskell-align-imports.el

 I also sort them with this:
 http://github.com/chrisdone/haskell-mode-exts/blob/master//haskell-sort-imports.el
 but it only works for one-line imports, which I advocate anyway.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-30 Thread Christopher Done
On 30 September 2010 16:47, Roel van Dijk vandijk.r...@gmail.com wrote:
 On the subject of coding style, I can work with almost any style as
 long as it is used somewhat consistently. Personally I try to optimize
 my code for ease of reading because I spend much more time reading
 code than writing. Aligning stuff vertically makes it easier to spot
 differences.

Me too. One thing that makes figuring out a code base hard is when the
code doesn't have explicit imports. Sometimes I can load the code in
GHCi and inspect the symbols manually, sometimes I can't. If the
import list explicitly said where stuff came from I wouldn't have to
deal with this.

Regarding style I've come to believe the best style is one that can be
enforced by your software, whatever it is. I don't want to have to
think about style.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-30 Thread Bas van Dijk
On Thu, Sep 30, 2010 at 5:15 PM, Christopher Done
chrisd...@googlemail.com wrote:
 ... One thing that makes figuring out a code base hard is when the
 code doesn't have explicit imports. Sometimes I can load the code in
 GHCi and inspect the symbols manually, sometimes I can't. If the
 import list explicitly said where stuff came from I wouldn't have to
 deal with this.

Indeed. I strictly use this style in all my projects. See the
following for example:

http://hackage.haskell.org/packages/archive/usb/0.6.0.1/doc/html/src/System-USB-Internal.html

I see it as a service to my readers. In order to find out where a
symbol is coming from they only need to scroll up and look it up in
the import list. Note that for further convenience I group the imports
by package so they don't need to figure out which package exports what
module.

I try to follow this style very strictly. I'm even using
NoImplicitPrelude to not miss any implicitly imported symbol. I also
import symbols from their defining module instead as from the Prelude.
For example, instead of importing fmap from the Prelude I import it
from Data.Functor. This ensures that when a reader looks up a symbol
she doesn't need to skim through a lot of unrelated code.

To be honest, there are cases where I violate my own rule. In the USB
module for example, I import Bindings.Libusb without explicitly
listing the used symbols. In this case I think it's justified because
I pretty much use all the symbols from that module and all symbols are
prefixed with 'c'libusb_' which clearly indicates where they are
coming from.

Note that, although I don't use it myself, the GHC flag:
-ddump-minimal-imports can help you with this style:

http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/separate-compilation.html#hi-options

Regards,

Bas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-30 Thread Henning Thielemann


On Thu, 30 Sep 2010, Bas van Dijk wrote:


On Thu, Sep 30, 2010 at 5:15 PM, Christopher Done
chrisd...@googlemail.com wrote:

... One thing that makes figuring out a code base hard is when the
code doesn't have explicit imports. Sometimes I can load the code in
GHCi and inspect the symbols manually, sometimes I can't. If the
import list explicitly said where stuff came from I wouldn't have to
deal with this.


Indeed. I strictly use this style in all my projects. See the
following for example:

http://hackage.haskell.org/packages/archive/usb/0.6.0.1/doc/html/src/System-USB-Internal.html

I see it as a service to my readers. In order to find out where a
symbol is coming from they only need to scroll up and look it up in
the import list. Note that for further convenience I group the imports
by package so they don't need to figure out which package exports what
module.


It is also necessary when you want x.y.* style version dependencies on 
packages that follow the package versioning policy.


http://www.haskell.org/haskellwiki/Import_modules_properly
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-30 Thread Bas van Dijk
Here are a few other styles I use:


* Unicode syntax and symbols

I use the UnicodeSyntax extension in all my projects. It allows you to
write nice Unicode syntax instead of the normal ASCII art. For
example: '→' instead of '-' and '∀' instead of 'forall'.

Additionally I'm a power-user of my brother's base-unicode-symbols
package[1]. I'm especially fond of the '∘' function composition
operator which you can use instead of '.'.

I believe UnicodeSyntax and symbols make code easier to read.
Although, it makes it slightly harder to write (see [2] for nice input
methods however).


* Use lambdas to group function arguments.

When I have a function which returns another function with a type that
is explicitly named, instead of listing all the arguments before the
=, I usually use a lambda to indicate that the function returns
another function. Take [3] for example:

readControl ∷ DeviceHandle → ControlAction ReadAction
readControl devHndl = \reqType reqRecipient request value index
→ \size timeout
→ ...

writeControl ∷ DeviceHandle → ControlAction WriteAction
writeControl devHndl = \reqType reqRecipient request value index
 → \input timeout
 → ...

where

type ControlAction α = RequestType
 → Recipient
 → Request
 → Value
 → Index
 → α

type ReadAction = Size → Timeout → IO (B.ByteString, TimedOut)
type WriteAction = B.ByteString → Timeout → IO (Size, TimedOut)

(I'm not sure if this has a negative effect on inlining tough.)

Regards,

Bas

[1] http://hackage.haskell.org/package/base-unicode-symbols
[2] http://haskell.org/haskellwiki/Unicode-symbols#Input_methods
[3] 
http://hackage.haskell.org/packages/archive/usb/0.6.0.1/doc/html/src/System-USB-Internal.html#readControl
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-30 Thread Henning Thielemann


On Thu, 30 Sep 2010, Bas van Dijk wrote:


I believe UnicodeSyntax and symbols make code easier to read.


If it can be read at all ... your Unicode symbol for '::' isn't shown in 
my terminal.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-30 Thread Donn Cave
Quoth Henning Thielemann lemm...@henning-thielemann.de,

 On Thu, 30 Sep 2010, Bas van Dijk wrote:

 I believe UnicodeSyntax and symbols make code easier to read.

 If it can be read at all ... your Unicode symbol for '::' isn't shown in 
 my terminal.

Same here, of course.  Win small, lose big.

Donn
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-30 Thread Bas van Dijk
On Thu, Sep 30, 2010 at 10:51 PM, Henning Thielemann
lemm...@henning-thielemann.de wrote:

 On Thu, 30 Sep 2010, Bas van Dijk wrote:

 I believe UnicodeSyntax and symbols make code easier to read.

 If it can be read at all ... your Unicode symbol for '::' isn't shown in my
 terminal.


Ah what a bummer! I thought most terminals where capable of showing a
wide range of Unicode these days.

For what it's worth: '::' shows up correctly in my terminals (Konsole
or urxvt with Bitstream Vera Sans Mono font).

Bas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-30 Thread Roel van Dijk
Here is a list of fonts that support that particular character:
http://www.fileformat.info/info/unicode/char/2237/fontsupport.htm

I think I'll add a little font overview to my unicode-symbols wiki
page. Most Unicode symbols that are useful in Haskell are not terribly
obscure and supported by a wide range of fonts.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-30 Thread Bas van Dijk
On Thu, Sep 30, 2010 at 11:24 PM, Bas van Dijk v.dijk@gmail.com wrote:
 For what it's worth: '::' shows up correctly in my terminals (Konsole
 or urxvt with Bitstream Vera Sans Mono font).

Turns out that I'm actually using the 'DejaVu Sans Mono' font...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-30 Thread Christopher Done
On 30 September 2010 21:02, Bas van Dijk v.dijk@gmail.com wrote:
 Note that, although I don't use it myself, the GHC flag:
 -ddump-minimal-imports can help you with this style:

 http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/separate-compilation.html#hi-options

Indeed, after discovering this I thought about writing a little Emacs
Lisp to have a keybinding for updating my imports using
-ddump-minimal-imports, so that I can write without explicit import
but then make it explicit when I'm done automatically. I forgot about
it so thanks for reminding me.

Ideally I would also write some functions that make automatic import
of a symbol easier. There are 4 problems with writing Haskell and
managing imports, as I see it, right now (I'll make up some names to
encapsulate these ideas):

1. Pretty printing: The order and spacing of imports.
2. Explicitness: The explicit naming of imported symbols, or qualification.
3. Discovery: Calculating where the symbol I'm using right now should
be imported from, and then adding that import either automatically or
with-confirmation.
4. Pruning: Removing unnecessary imports, and merging imports which
are the same.

I made some functions to make it easier to jump back and forth to
imports, but now I don't really want to manually write out an import
statement again. I'd prefer to have Emacs present me with options,
i.e., these are the modules that export that type/symbol/class, pick
one (with ido/fuzzy completion) and then it adds the import line at
the correct place with the desired spacing and with the necessary
import.

You also sometimes refactor part of a module to another module, and
then you need to copy over all the necessary imports. I tend to copy
all my imports over and then remove the ones GHCi tells me aren't
necessary. So, one solution to make this automatic copy over all the
imports from the current module and then prune.

Perhaps I will attempt some of this on the weekend, as it's the
biggest pain I have right now writing Haskell code. I spend a lot of
time just maintaining my imports.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-30 Thread Evan Laforge
Sorry, forgot to reply to all

 You also sometimes refactor part of a module to another module, and
 then you need to copy over all the necessary imports. I tend to copy
 all my imports over and then remove the ones GHCi tells me aren't
 necessary. So, one solution to make this automatic copy over all the
 imports from the current module and then prune.

 Perhaps I will attempt some of this on the weekend, as it's the
 biggest pain I have right now writing Haskell code. I spend a lot of
 time just maintaining my imports.

Same here, though I use exclusively qualified imports so it's not such
a hassle.  But it
adds busywork when you start a new module or want to split some code
into a new one.

The one feature I really like in eclipse is a key you hit to clean up
the imports.  It removes the unused ones, and tries to find imports
for symbols that aren't in scope.  If there are multiple
possibilities, it asks which one.  It even does this automatically
when you copy and paste code between files.  I would love something
like this for haskell.

It's easier in my case because I use exclusively qualified imports and
almost always name them as the last component after the dot, so if you
parse the source file and find 'M.a' and there's no 'import qualified
.. as M' then you just search for 'M' modules.  If I were writing this
(and I may take a shot some day), I'd write a standalone program that
filters a file, that way it works no matter what editor you use.  And
why write it in elisp when you could write it in haskell, and have
access to haskell-src?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-29 Thread Andrew Coppin

 On 29/09/2010 02:18 PM, Henning Thielemann wrote:

Andrew Coppin wrote:

Tastes do indeed vary. To me, both of these are incorrect, and the 
correct way is


  data Foo a b =
  Fooa   |
  Bar  b |
  Foobar a b
deriving (Eq, Ord)


The truth is: Given the separator style of constructor definition, 
there is no correct way to format those declarations. :-) The correct 
way would be to allow terminator style.


Well, yes, there is that. (And this isn't the only place in the syntax 
where it applies either. Tried editing export lists lately? Or Cabal 
module lists?)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-28 Thread Ben Millwood
On Tue, Sep 28, 2010 at 5:55 AM, Evan Laforge qdun...@gmail.com wrote:

 I write haskell and python in a proportional font and it hasn't yet
 let to tabs, so no pain so far :)
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


I like writing proportional haskell, but I haven't worked out how to
do let-blocks in ways that look nice - the tactic I use for do and
where of breaking the line immediately tends to look a little odd,
especially if you're only making about one binding.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-27 Thread Henning Thielemann
Alexander Solla schrieb:

 I used a modified version of the best practices described by the Perl
 people for Perl code.  Like things go under like things is the most
 important rule to follow.  This rule, in other words, is a convention to
 make your code as tabular as possible.  Also, most expressions have an
 outermost connective.  I tend to align them:
 
 Consider:
 
 data Foo a b = Fooa
  | Bar  b
  | Foobar a b
 
 That's not so nice looking now, but consider what happens when you have
 four or five arguments:

This indentation relies on Foo remaining Foo in the future. If you alter
Foo then you have to move the block of constructors as well. This gives
line changes in a versioning system where nothing actually has changed.
The style

data Foo a b =
 Fooa
   | Bar  b
   | Foobar a b

avoids this, at least for the type name Foo.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-27 Thread Daniel Fischer
On Monday 27 September 2010 14:52:18, Henning Thielemann wrote:
 data Foo a b =
      Foo    a
    | Bar      b
    | Foobar a b

 avoids this, at least for the type name Foo.

Tastes vary, but I find that ugly. I much rather have the '=' aligned with 
the '|'.

data Foo a b
= Foo  a
| Barb
| Foobar  a b
  deriving (Eq, Ord)

There, that looks good.

With the one exception that as a rule, in a multi-constructor type, none of 
the constructors should be identical to the type name (IMO).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-27 Thread Evan Laforge
 data Foo a b
    = Foo      a
    | Bar        b
    | Foobar  a b
      deriving (Eq, Ord)

 There, that looks good.

There is a trap if you do a similar thing with records:

data Foo = Foo
  { a :: Int
  , b :: Int
  }

If you use '-- |' style haddock it can't go on 'a'.  Since I tend to
want to put '-- |' on every field, I have to put the '{' on the
previous line.

As for other stuff, I don't like the vertical lining up thing.  It's
too much work to type in, causes too much realigning when the top line
changes, sometimes causes things to get too far right, and breaks
entirely with proportional fonts.  A plain indent as advocated above
avoids all those problems.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-27 Thread Daniel Fischer
On Monday 27 September 2010 18:09:08, Evan Laforge wrote:
  data Foo a b
     = Foo      a
     | Bar        b
     | Foobar  a b
       deriving (Eq, Ord)
 
  There, that looks good.

 There is a trap if you do a similar thing with records:

 data Foo = Foo
   { a :: Int
   , b :: Int
   }

 If you use '-- |' style haddock it can't go on 'a'.  Since I tend to
 want to put '-- |' on every field, I have to put the '{' on the
 previous line.

Hm, yes. I always use '-- ^' haddock comments for record fields, so that 
didn't occur to me.


 As for other stuff, I don't like the vertical lining up thing.  It's

I haven't tried it yet. I think aligning corresponding fields has 
advantages - it makes it rather obvious to see which constructor uses which 
parameter types in many cases.
On the other hand, with many fields you get a very scattered picture if 
some constructors only have few. That looks ugly and isn't easy to take in 
at a glance.
I don't think I'll adopt it, but I plan to try it out.

 too much work to type in, causes too much realigning when the top line
 changes, sometimes causes things to get too far right,

Yep

 and breaks entirely with proportional fonts.

Not relevant for me, when looking at Haskell or Python code, I value my 
fixed-width font, it just looks too weird in proportional fonts.

 A plain indent as advocated above avoids all those problems.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-27 Thread Andrew Coppin

 On 27/09/2010 02:44 PM, Daniel Fischer wrote:

On Monday 27 September 2010 14:52:18, Henning Thielemann wrote:

data Foo a b =
  Fooa
| Bar  b
| Foobar a b

avoids this, at least for the type name Foo.

Tastes vary, but I find that ugly. I much rather have the '=' aligned with
the '|'.

data Foo a b
 = Foo  a
 | Barb
 | Foobar  a b
   deriving (Eq, Ord)

There, that looks good.


Tastes do indeed vary. To me, both of these are incorrect, and the 
correct way is


  data Foo a b =
  Fooa   |
  Bar  b |
  Foobar a b
deriving (Eq, Ord)

It honestly annoys me that Haddock disagrees with me on this point...

(It also irritates me that almost all Haskell identifiers are 
camel-case, but with an inital lowercase letter. IMHO, the correct thing 
to do is use camel-case for identifiers that must begin with an 
uppercase letter, and underscores for identifiers that must begin with a 
lowercase letter. Of course, my opinion has no effect on the Prelude and 
so forth.)


I generally try to structure my code so that all blocks indent by 2 
spaces, and the size of indentation never depends on the length of an 
identifier. In other words, none of this:


  foo x y z = do
  thing1 x
  thing2 x y
  thing3 z
  ...

Do that a few times and you rapidly end up with lines 300 characters 
wide. (!) Instead, I prefer


  foo x y z = do
thing1 x
thing2 x y
thing3 z
...

But, as they say, everybody has their own ideas about style. I think the 
most important point must surely be that any style is applied 
*consistently*...


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-27 Thread Max Rabkin
On Mon, Sep 27, 2010 at 22:57, Andrew Coppin
andrewcop...@btinternet.com wrote:
  data Foo a b =
      Foo    a   |
      Bar      b |
      Foobar a b
    deriving (Eq, Ord)

 It honestly annoys me that Haddock disagrees with me on this point...

I disagree with you too, and so does your version control (if I'm
wrong, please tell me, so I can switch). If you add a constructor, you
have to make a change to the line containing the old last constructor,
even though you didn't actually change that line.

Also, either your pipes don't line up, or you violate your own rule

 I generally try to structure my code so that all blocks indent by 2 spaces, 
 and the size of indentation never depends on the length of an identifier.

...except that the spaces here are not indentation.

--Max

(exhausted from real work, so taking some time out to paint the bikeshed)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-27 Thread aditya siram
How do you guys indent long function arguments? I run into this all
the time with the 'maybe' function which takes 3 arguments:
maybe :: b - (a - b) - Maybe a - b
I usually end up doing things like (pretend the arguments are aligned
if you're not using a monospace font to view this):
maybe do-if-Nothing
  (\x - do-if-Just x)
  maybe-value
This gets a little unwieldly if the any of the arguments stretch over
one line like:

maybe do-if-Nothing
  (\x - ...
  ...
  something
  )
  maybe-value


Any advice on indentation? I could avoid the problem by adding a 'let'
or 'where' but sometimes I like to show the entire function without
the user having to scan another definition.
-deech




On Mon, Sep 27, 2010 at 3:57 PM, Andrew Coppin
andrewcop...@btinternet.com wrote:
  On 27/09/2010 02:44 PM, Daniel Fischer wrote:

 On Monday 27 September 2010 14:52:18, Henning Thielemann wrote:

 data Foo a b =
      Foo    a
    | Bar      b
    | Foobar a b

 avoids this, at least for the type name Foo.

 Tastes vary, but I find that ugly. I much rather have the '=' aligned with
 the '|'.

 data Foo a b
     = Foo      a
     | Bar        b
     | Foobar  a b
       deriving (Eq, Ord)

 There, that looks good.

 Tastes do indeed vary. To me, both of these are incorrect, and the correct
 way is

  data Foo a b =
      Foo    a   |
      Bar      b |
      Foobar a b
    deriving (Eq, Ord)

 It honestly annoys me that Haddock disagrees with me on this point...

 (It also irritates me that almost all Haskell identifiers are camel-case,
 but with an inital lowercase letter. IMHO, the correct thing to do is use
 camel-case for identifiers that must begin with an uppercase letter, and
 underscores for identifiers that must begin with a lowercase letter. Of
 course, my opinion has no effect on the Prelude and so forth.)

 I generally try to structure my code so that all blocks indent by 2 spaces,
 and the size of indentation never depends on the length of an identifier. In
 other words, none of this:

  foo x y z = do
              thing1 x
              thing2 x y
              thing3 z
              ...

 Do that a few times and you rapidly end up with lines 300 characters wide.
 (!) Instead, I prefer

  foo x y z = do
    thing1 x
    thing2 x y
    thing3 z
    ...

 But, as they say, everybody has their own ideas about style. I think the
 most important point must surely be that any style is applied
 *consistently*...

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-27 Thread John D. Ramsdell
I just see what Emacs Haskell mode suggests, and pick one of its suggestions.

John
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-27 Thread Gregory Collins
Evan Laforge qdun...@gmail.com writes:

 As for other stuff, I don't like the vertical lining up thing.  It's
 too much work to type in, causes too much realigning when the top line
 changes, sometimes causes things to get too far right, and breaks
 entirely with proportional fonts.  A plain indent as advocated above
 avoids all those problems.

I'm going to go ahead and offer a contrary viewpoint -- lining up code
vertically makes it so much easier to read that the extra work involved
(trivial, if you have a half-decent text editor) is more than worth
it. Also, if you're reading code in a proportional font, you're doing
it wrong.

G
-- 
Gregory Collins g...@gregorycollins.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-27 Thread Evan Laforge
On Mon, Sep 27, 2010 at 2:09 PM, aditya siram aditya.si...@gmail.com wrote:
 How do you guys indent long function arguments? I run into this all
 the time with the 'maybe' function which takes 3 arguments:
 maybe :: b - (a - b) - Maybe a - b
 I usually end up doing things like (pretend the arguments are aligned
 if you're not using a monospace font to view this):
 maybe do-if-Nothing
          (\x - do-if-Just x)
          maybe-value
 This gets a little unwieldly if the any of the arguments stretch over
 one line like:

 maybe do-if-Nothing
          (\x - ...
                  ...
                  something
          )
          maybe-value

I do basically like that only I don't try to line up vertically.  One
indent to continue a line, nested indent for a nested continued line.
However, I tend to factor out the long values with let or where.  I
find it hard to read when everything is coming from some third
argument which is a tiny nub at the end of a giant expression.  And if
you factor out the if just case, you can also more easily make the
transition to monadic style if you find yourself with too many
'maybe's in sequence.  If you can eta-reduce that last arg, though, it
can be pretty:

defaulted = maybe deflt $ \v - [ do ]
stuff
...

One place I do have difficulty is in pattern matching, because you
can't factor that out as easily.  I do use view patterns sometimes for
that, but only when it's a common pattern.  So I wind up with a nested
indent:

function too many arguments
with (Complicated (Pattern matching)) =
  definition

case x of
Pattern (Match
Is Way Too Long) -
stuff

It's ugly but rare.  'let' within a 'do' is a particular culprit
because right off the bat you've got one indent for 'do' and then the
'let' forces two more indents.  Sometimes the too many arguments can
be factored into a single type, sometimes nasty nested pattern matches
can be factored into view patterns or a data structure that reflects
its access pattern rather than building pattern or whatever.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-27 Thread Felipe Lessa
On Mon, Sep 27, 2010 at 6:28 PM, Gregory Collins
g...@gregorycollins.net wrote:
 Also, if you're reading code in a proportional font, you're doing
 it wrong.

You may have nice codes using proportional fonts using LaTeX package
'listings'.  Even in a proportional font it lines things up.  Note,
however, that you need to write *your* LaTeX source code in a
fixed-width font for 'listings' to understand where things should be
lined up.

Unfortunately we don't have this mode in any editor as far as I know.
And even if we did, I don't know how the same code would be viewed in
another editor.  Reading 'listings'-style LaTeX isn't funny, much less
writing.

Cheers! :)

-- 
Felipe.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-27 Thread Evan Laforge
 I'm going to go ahead and offer a contrary viewpoint -- lining up code
 vertically makes it so much easier to read that the extra work involved

I haven't noticed it being easier to read, but I don't like syntax
highlighting either, and lots of people seem to like that too.  Taste
is taste.

 (trivial, if you have a half-decent text editor) is more than worth
 it. Also, if you're reading code in a proportional font, you're doing
 it wrong.

The editor is 'acme', which a programming editor.  It has support for
fixed fonts too, but proportional is often more pleasant.  You can fit
a lot more on a line, but of course that can inconvenience the
80-column people :)  It's worth a try if you haven't already.  I think
it's more than just half-decent, but it doesn't have any fancy
vertical line up type features either.

Anyway, it's definitely a minority use case, but that's a position
haskellers should be used to :)  And I admit I use a lot more
fixed-width vim nowadays, so it's not a super big issue to me.  But I
do like it how everything looks nice when I occasionally do open up my
project in acme because I miss some of its features.

Vim and fixed width is especially ugly with unicode, so I'd think
haskellers or agda-ists who appreciate a good pageful of cryptic math
symbols to scare off the plebes would enjoy a nice proportional font
using editor.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-27 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 9/27/10 17:07 , Max Rabkin wrote:
 On Mon, Sep 27, 2010 at 22:57, Andrew Coppin andrewcop...@btinternet.com 
 wrote:
  data Foo a b =
  Fooa   |
  Bar  b |
  Foobar a b
deriving (Eq, Ord)
 
 Also, either your pipes don't line up, or you violate your own rule

They line up fine in a fixed width font.  Programming in any
indentation-sensitive language in a proportional font leads inevitably to
use of tabs to make things line up properly, which leads directly to pain.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkyhHNcACgkQIn7hlCsL25XKjwCgjlxdAK1RTimZhFb0nzyYo5lu
pXAAoLKdcuZ7foV+uM0s9QtvabFopuJl
=WCR4
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-27 Thread Donn Cave
Quoth Brandon S Allbery KF8NH allb...@ece.cmu.edu,
...
 They line up fine in a fixed width font.  Programming in any
 indentation-sensitive language in a proportional font leads inevitably to
 use of tabs to make things line up properly, which leads directly to pain.

I haven't noticed urgent problems with indentation, per se.  I'm not
programming in proportional fonts, but of course when I look at this
stuff here it's email, not a programming editor, and the fonts are
proportional.  Maybe I'm lucky with the fonts on my platform, but the
indentation is fine.  All I expect is that indentation levels compare
correctly to themselves:  i.e., any two lines indented to the same
level are indented the same distance and indented to different levels
they are indented an appropriately lesser or greater distance.

(That's slightly less rigorous than Haskell's layout requires, though,
isn't it?  I'm not sure.  If it does, anyway my personal coding style
is not to depend on alignment for structure, but only relative
indentation.)

The present problem involves alignments that are superfluous to
Haskell's indentation requirement.  Vertical alignment past the
indentation does indeed dictate use of fixed width fonts, for editor
and all display media.  Not nearly worth it in my opinion, but
obviously some would disagree.

Donn
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-27 Thread Evan Laforge
 Also, either your pipes don't line up, or you violate your own rule

 They line up fine in a fixed width font.  Programming in any
 indentation-sensitive language in a proportional font leads inevitably to
 use of tabs to make things line up properly, which leads directly to pain.

I write haskell and python in a proportional font and it hasn't yet
let to tabs, so no pain so far :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-26 Thread Petr Pudlak

Hi Johan,

On Sat, Sep 25, 2010 at 01:44:07PM +0200, Johan Tibell wrote:

Quite a few people follow my style guide

   http://github.com/tibbe/haskell-style-guide/blob/master/haskell-style.md

which codifies the style used in Real World Haskell, bytestring, text,
and a few other libraries.


Thanks for sharing the link, it's quite helpful. It's just what I was 
looking for. 

One more thought: Do you also have some recommendations for formatting 
'let ... in ...' expressions?


 Best regards,
 Petr
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-26 Thread Johan Tibell
I usually align the in under the let.
On Sep 26, 2010 11:40 AM, Petr Pudlak d...@pudlak.name wrote:
 Hi Johan,

 On Sat, Sep 25, 2010 at 01:44:07PM +0200, Johan Tibell wrote:
Quite a few people follow my style guide

 http://github.com/tibbe/haskell-style-guide/blob/master/haskell-style.md

which codifies the style used in Real World Haskell, bytestring, text,
and a few other libraries.

 Thanks for sharing the link, it's quite helpful. It's just what I was
 looking for.

 One more thought: Do you also have some recommendations for formatting
 'let ... in ...' expressions?

 Best regards,
 Petr
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-26 Thread Henning Thielemann
Petr Pudlak schrieb:

 sometimes I have doubts how to structure my Haskell code - where to
 break lines, how much to indent, how to name functions and variables
 etc. Are there any suggested/recommended coding conventions?

Coding conventions are often a matter of individual taste. You may find
some suggestions under
  http://www.haskell.org/haskellwiki/Category:Style
and choose the ones that you like.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-26 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 9/25/10 11:06 , Donn Cave wrote:
 Though it's common practice for sure, maybe universal, does the
 Don't insert a space after a lambda rule make sense?
 
 I found it confusing at first sight, because of course it looks

More to the point, some editors find it confusing.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkyf4AIACgkQIn7hlCsL25XhtQCgnm9XsAGq6lmJkZCg5U1Of6hK
Xb0AoJyqoVU9lI6QOJPQ6729NmS4kNvS
=8eeh
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-26 Thread Johan Tibell
On Sun, Sep 26, 2010 at 12:50 PM, Henning Thielemann
schlepp...@henning-thielemann.de wrote:
 Coding conventions are often a matter of individual taste. You may find
 some suggestions under
  http://www.haskell.org/haskellwiki/Category:Style
 and choose the ones that you like.

Absolutely. However, having a consistent style, whatever it might be,
does bring some benefits and hence there are style guides. :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-26 Thread Alexander Solla

 On 09/25/2010 02:24 AM, Petr Pudlak wrote:

Hi,

sometimes I have doubts how to structure my Haskell code - where to 
break lines, how much to indent, how to name functions and variables 
etc. Are there any suggested/recommended coding conventions? I 
searched a bit and I found a few articles and discussions:


I used a modified version of the best practices described by the Perl 
people for Perl code.  Like things go under like things is the most 
important rule to follow.  This rule, in other words, is a convention to 
make your code as tabular as possible.  Also, most expressions have an 
outermost connective.  I tend to align them:


Consider:

data Foo a b = Fooa
 | Bar  b
 | Foobar a b

That's not so nice looking now, but consider what happens when you have 
four or five arguments:


type Label = String
type Address = String

data Foo a b = Foo  (Maybe Label)  Address a
 | Bar Label b
 | Foobar  Label   Address a b

This is rather neat.  Instead of focusing effort on parsing the source, 
we can merely compare lines for the differences in logic they embody.  
Compare it with an un-normalized definition:


data Foo a b = Foo (Maybe Label) Address a
 | Bar Label b
 | Foobar Label Address a b

Quick, which one of those has a b in it?  Moreover, it make 
editing/refactoring easier with tools like Vim (with its visual block 
mode) and TextMate.  I'm sure Emacs, etc have block editing modes too.


To that end, I try to keep in the style of this style.  For let-in 
pairs, I do:


expression a = let exp  = blah_blah  a
   exp' = blah_blah' a
in (exp ++ exp')

I usually keep parentheses aligned as well, if a pair won't fit in a 
line.  That's one of the more obvious consequences of my convention.  
Monadic operators are worth keeping together, for similar reasons as 
keeping parentheses aligned.


action = first = second = third -- :fits on one line

-- Steps added:
action = first
= second
= third
= fourth
= fifth

You can jump into do notation pretty easily from there, by deleting the 
= operators, and sticking a 'do' before first.


Remember to treat values, functions, and monadic actions as servers 
that respond to your requests.  This is the easiest way to maximize the 
value of Haskell's laziness.


Also, and finally, remember that a function is a special kind of join on 
data types.  (A many-to-one join, in terms of the relational algebra as 
spoken of by database people).  My approach makes it easy to abstract 
operators out of the act of reading.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-26 Thread Donn Cave
Quoth Alexander Solla a...@2piix.com,
...
 That's not so nice looking now, but consider what happens when you have 
 four or five arguments:

 type Label = String
 type Address = String

 data Foo a b = Foo  (Maybe Label)  Address a
   | Bar Label b
   | Foobar  Label   Address a b

 This is rather neat.  Instead of focusing effort on parsing the source, 
 we can merely compare lines for the differences in logic they embody.  

Note that it depends on a mono-spaced font.  Works as intended
in my terminal emulator window, and anywhere you or I have gone
to the trouble, but my initial look at it was in my email, which
as usual is a proportional font, and nothing lines up after the
first column.

Donn
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-25 Thread Johan Tibell
On Sat, Sep 25, 2010 at 11:24 AM, Petr Pudlak d...@pudlak.name wrote:
 sometimes I have doubts how to structure my Haskell code - where to break
 lines, how much to indent, how to name functions and variables etc. Are
 there any suggested/recommended coding conventions? I searched a bit and I
 found a few articles and discussions:

Quite a few people follow my style guide

http://github.com/tibbe/haskell-style-guide/blob/master/haskell-style.md

which codifies the style used in Real World Haskell, bytestring, text,
and a few other libraries.

-- Johan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-25 Thread Donn Cave
Though it's common practice for sure, maybe universal, does the
Don't insert a space after a lambda rule make sense?

I found it confusing at first sight, because of course it looks
like something else - in \n m - ..., to the uninitiated it
represents a newline, for example.  Now that I understand that
it's a symbolic keyword, it's an odd way to treat it.  This has
probably come up before, so feel free to ignore, I'm just saying.

The white space I have trouble deciding on is one-line record
syntax --  ARecord { aField = a }, or maybe ARecord {aField = a}.

Donn
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-25 Thread Johan Tibell
On Sat, Sep 25, 2010 at 5:06 PM, Donn Cave d...@avvanta.com wrote:
 Though it's common practice for sure, maybe universal, does the
 Don't insert a space after a lambda rule make sense?

 I found it confusing at first sight, because of course it looks
 like something else - in \n m - ..., to the uninitiated it
 represents a newline, for example.  Now that I understand that
 it's a symbolic keyword, it's an odd way to treat it.  This has
 probably come up before, so feel free to ignore, I'm just saying.

I think I lean more towards surrounding \ with spaces nowadays.

 The white space I have trouble deciding on is one-line record
 syntax --  ARecord { aField = a }, or maybe ARecord {aField = a}.

I always do the former and I think it's the more common style.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe