Readable Haskell

Hi, I have been writing Haskell in my spare time for a couple of years now, but when I showed some code lately to a friend he remarked that he didn't find it very readable. Actually I agree, when I look at my own code of a couple of months old I have trouble figuring out too what exactly it is doing. I'm coming from a Java and Scala background and there, especially for Java, are some generally accepted best practices that make sure that your teammates don't have too much trouble reading your code. E.g. write short functions with a single responsibility, use variable, class and function names that explain what they are meant for, etc. I think some of those best practices, like short functions with single responsibility, are useful for Haskell as well. But Haskell is a different language than Java and has its own strong points and pitfalls regarding readability, so it probably needs different coding standards as well. I have been looking on the Internet if I could find some tips about improving readability but all I could find was http://www.haskellforall.com/. Although there are some useful tips in there, this site seems to be aimed at making Haskell easier to read for newcomers from other languages. What I am interested in are tips from real projects that are built by real teams. Does anybody have any tips, or are there some sites or books that I could read about this topic? Thanks, Misja

Generally write functions with meaningfull names. Using symbols should be understandable and clear. Generally Haskell is easy to read. Greets, Branimir. On 9/19/20 5:02 PM, Misja Alma wrote:
Hi,
I have been writing Haskell in my spare time for a couple of years now, but when I showed some code lately to a friend he remarked that he didn't find it very readable. Actually I agree, when I look at my own code of a couple of months old I have trouble figuring out too what exactly it is doing.
I'm coming from a Java and Scala background and there, especially for Java, are some generally accepted best practices that make sure that your teammates don't have too much trouble reading your code. E.g. write short functions with a single responsibility, use variable, class and function names that explain what they are meant for, etc.
I think some of those best practices, like short functions with single responsibility, are useful for Haskell as well. But Haskell is a different language than Java and has its own strong points and pitfalls regarding readability, so it probably needs different coding standards as well.
I have been looking on the Internet if I could find some tips about improving readability but all I could find was http://www.haskellforall.com/. Although there are some useful tips in there, this site seems to be aimed at making Haskell easier to read for newcomers from other languages. What I am interested in are tips from real projects that are built by real teams. Does anybody have any tips, or are there some sites or books that I could read about this topic?
Thanks, Misja
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Sat, 19 Sep 2020, Misja Alma wrote:
Does anybody have any tips, or are there some sites or books that I could read about this topic?
It may be a bit old but we have some articles on style in the Haskell Wiki: https://wiki.haskell.org/Category:Style https://wiki.haskell.org/Category:Idioms

Thanks, these links are really useful! This definitely answers part of my question. But what would still be really useful are some more or less generally accepted best practices about variable naming, indentation, when to use nested functions vs when to prefer keeping functions short, etc with regards to readability. On Sat, 19 Sep 2020 at 17:10, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Sat, 19 Sep 2020, Misja Alma wrote:
Does anybody have any tips, or are there some sites or books that I could read about this topic?
It may be a bit old but we have some articles on style in the Haskell Wiki: https://wiki.haskell.org/Category:Style https://wiki.haskell.org/Category:Idioms

For indentation and very mechanical formatting, I suggest just using something like hindent, brittany or ormolu (all available at your local Hackage). For naming, I follow Chris Done's suggestion: https://chrisdone.com/posts/german-naming-convention/ On Sat, 19 Sep 2020, at 4:32 PM, Misja Alma wrote:
Thanks, these links are really useful! This definitely answers part of my question.
But what would still be really useful are some more or less generally accepted best practices about variable naming, indentation, when to use nested functions vs when to prefer keeping functions short, etc with regards to readability.
On Sat, 19 Sep 2020 at 17:10, Henning Thielemann
wrote: On Sat, 19 Sep 2020, Misja Alma wrote:
Does anybody have any tips, or are there some sites or books that I could read about this topic?
It may be a bit old but we have some articles on style in the Haskell Wiki: https://wiki.haskell.org/Category:Style https://wiki.haskell.org/Category:Idioms
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Sat, 19 Sep 2020, Oliver Charles wrote:
For naming, I follow Chris Done's suggestion: https://chrisdone.com/posts/german-naming-convention/
Interesting perspective on German language. :-) Btw. I would prefer ColumnExpression.update. Or even ColExp.update because at the top of the module I would have import qualified ColumnExpression as ColExp

For naming, I follow Chris Done's suggestion: https://chrisdone.com/posts/german-naming-convention/
Thanks! I didn't know it had this funny name, but the German name
convention is also widely used in the Java world.
But I wonder how well it works in Haskell, because unlike Java, in Haskell
a lot of stuff can happen in a single line. With those long variable names,
you'd have to
break those lines several times. I haven't tried it yet, but I wonder how
readable that is in Haskell?
Or am I looking at the wrong problem here, and should I first of all try to
have as little happening in a single line of Haskell as possible?
On Sat, 19 Sep 2020 at 18:22, Oliver Charles
For indentation and very mechanical formatting, I suggest just using something like hindent, brittany or ormolu (all available at your local Hackage).
For naming, I follow Chris Done's suggestion: https://chrisdone.com/posts/german-naming-convention/
On Sat, 19 Sep 2020, at 4:32 PM, Misja Alma wrote:
Thanks, these links are really useful! This definitely answers part of my question.
But what would still be really useful are some more or less generally accepted best practices about variable naming, indentation, when to use nested functions vs when to prefer keeping functions short, etc with regards to readability.
On Sat, 19 Sep 2020 at 17:10, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Sat, 19 Sep 2020, Misja Alma wrote:
Does anybody have any tips, or are there some sites or books that I could read about this topic?
It may be a bit old but we have some articles on style in the Haskell Wiki: https://wiki.haskell.org/Category:Style https://wiki.haskell.org/Category:Idioms
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Sat, Sep 19, 2020 at 07:07:38PM +0200, Misja Alma wrote:
But I wonder how well it works in Haskell, because unlike Java, in Haskell a lot of stuff can happen in a single line.
One idiom for making "a lot of stuff in a single line" easier to read is seen in: https://hackage.haskell.org/package/streaming-attoparsec-1.0.0.1/docs/Data-A... ... import Data.Function ((&)) main :: IO () main = Q.getContents -- raw bytes & AS.parsed lineParser -- stream of parsed `Maybe Int`s; blank lines are `Nothing` & void -- drop any unparsed nonsense at the end -- [1] & S.split Nothing -- split on blank lines & S.maps S.concat -- keep `Just x` values in the sub-streams (cp. catMaybes) & S.mapped S.sum -- sum each substream & S.print -- stream results to stdout lineParser = Just <$> A.scientific <* A.endOfLine <|> Nothing <$ A.endOfLine Here, the function composition flows from left to right, in fact top to bottom, rather than right to left (bottom to top over multiple lines). The key ingredient is the (&) operator which puts the argument on the left and the function on the right. I've also seen (the first borrowed from F#): (|>): a -> (a -> b) -> b (|.>): (a -> b) -> (b -> c) -> c (|$>) f a -> (a -> b) -> f b (|*>) f a -> f (a -> b) -> f b And of course Conduit's (.|) is another instance of left-to-right style for expressing long composition chains. Returning to the streaming example, since in `streaming` transformations of streams are performed via function application (no new operator like Conduit's (.|)), the left-to-right style uses (&). Of course even with the flow made clear, and names well chosen, one still has to come to grips with some rather powerful, highly polymorphic idioms, whose purpose in each context may warrant a comment in code that is to be accessible to those still learning the ropes. The somewhat non-obvious "void" here is but a mild example. -- Viktor. [1] One slightly non-obvious thing at first blush about streams is that "void" does not perturb the content of the stream, it only drops the stream's terminal value. Streams are functors in that terminal value, so it turns out, surprisingly at first, that the two variants of "print the stream" below are identical. s :: Show a => Stream (Of a) IO r s = ... -- The relevant functor here is: F r = (Stream (Of a) IO) r -- thus, void s :: Stream (Of a) IO () S.print . void $ s -- same as void . S.print $ s So, for a reader not steeped in the streaming library, one might even comment on the role of "void" in more detail: ... & AS.parsed lineParser -- stream of parsed `Maybe Int`s; blank lines are `Nothing` & void -- Replace the stream `Return` value `r` with `()` -- discarding parser errors, see 'AS.parsed'. ... So that nobody is left wondering at stream processing continuing past "void", which in more mundate contexts one expects to not return anything useful to be further processed. This briefly caught me by surprise in the "all in one line" right-to-left example at the end of the document: S.print . void $ AS.parsed (A.scientific <* A.many' A.space) "12.3 4.56 78.9"

main :: IO () main = Q.getContents -- raw bytes & AS.parsed lineParser -- stream of parsed `Maybe Int`s; blank lines are `Nothing` & void -- drop any unparsed nonsense at the end -- [1] & S.split Nothing -- split on blank lines & S.maps S.concat -- keep `Just x` values in the sub-streams (cp. catMaybes) & S.mapped S.sum -- sum each substream & S.print -- stream results to stdout
There's still quite a bit that can be improved here. First of all: comments are good. But whenever you write a comment, ask yourself "could I choose a better name instead?" Make the code self-documenting at all usage sites by choosing a good name once. It's a good idea for every language, but this piece of code is a good example of how to apply it. So, first step: main ∷ IO () main = Q.getContents & parseLines & dropUnparsed -- Add the explanation/link definition side & splitOnBlankLines & catMaybes' -- why write "it's catMaybes", when you could just write "catMaybes"? & S.mapped S.sum & S.print Do you need more functions this way to store the names? Yes. Which is a good thing, because they might be reusable. Of course there's a limit; if every function fits in half a line, you've probably gone too far. Second step: Thinking from left to right is a remainder from thinking imperatively. If you just turn around the top level of the code, the reader is forced to a game of ping pong while reading, so it can even make it harder to understand. So let's get rid of that (&) crowbar. main ∷ IO ()main = S.print . S.mapped S.sum . catMaybes' -- by the way, there's probablya better name for what it's actually doing. "dropBlankLines", maybe? . splitOnBlankLines . dropUnparsed . parseLines $ Q.getContents There's more reasons why going against Haskell's natural grain is a bad idea, and you provided the perfect hook to talk about it:
(|>): a -> (a -> b) -> b (|.>): (a -> b) -> (b -> c) -> c (|$>) f a -> (a -> b) -> f b (|*>) f a -> f (a -> b) -> f b
Operators have the inherent problem that there aren't many symbols to choose from. That means that almost all operators are overloaded. For example, (|>) will be confused with the one from Data.Sequence. Yes, there's unicode. I love unicode (see that sneaky little "∷" up there?) so I've tried using Unicode in operators before, but one single person using the project had their device set to a C locale and so my whole library was search-and-replaced. It's still 1968 out there, so there's like 10 symbols to choose from. And even if you could use more symbols, operators still have the inherent problem that they can't contain any letters. What exactly does (>>?$>) mean? Or (|>||>)? Or (<<*>@)? So why not rely on the operators that are widely used instead of crowbaring new ones in just so that we can keep programming in C.

On Sun, Sep 20, 2020 at 08:37:28PM +0200, MarLinn wrote:
main :: IO () main = Q.getContents -- raw bytes & AS.parsed lineParser -- stream of parsed `Maybe Int`s; blank lines are `Nothing` & void -- drop any unparsed nonsense at the end -- [1] & S.split Nothing -- split on blank lines & S.maps S.concat -- keep `Just x` values in the sub-streams (cp. catMaybes) & S.mapped S.sum -- sum each substream & S.print -- stream results to stdout
There's still quite a bit that can be improved here.
Yes, that short example (from a module's documentation) was chosen to illustrate left-to-right style, and the direct use of helper functions from `streaming` also helps to illustrate those functions in use. So in the context of module documentation, it is actually helpful to not replace the helpers with semantically appropriate (but implementation opaque) aliases. As for objections to use of left to right notation, in representing chains of transformations, we're going to have to disagree about that. -- Viktor.

Am 19.09.20 um 18:22 schrieb Oliver Charles:
For naming, I follow Chris Done's suggestion: https://chrisdone.com/posts/german-naming-convention/
FWIW, I tend to disagree with the position presented in this blog, at least in the generality in which it is stated. Yes, long names can be useful to enhance readability, but this is mostly the case when naming highly specific things. In Haskell, core algorithms often implement some algebraic theory. It is not by accident that mathematical formulae, including applications in the natural sciences, almost exclusively use single letters or very short names. Understanding such formulae at a glance requires familiarity with the notational conventions used, but once you have achieved that familiarity, the short names actually /improve/ readability, assuming the naming convention is applied in a consistent manner. It is also no accident that formulae typically make up only a part of the complete text. A complex formula needs to be accompanied by precise definitions and explanations. Whenever you write code for which it is not immediately obvious why it was done in exactly this way, add a comment that explains what is going on! To illustrate my point, here is some code that implements a highly non-trivial algebra I wrote some time ago: https://hub.darcs.net/darcs/darcs-screened/browse/src/Darcs/Patch/V3/Core.hs... I think using longer names in this code would be awkward and distracting. Also note that the naming convention is documented: https://hub.darcs.net/darcs/darcs-screened/browse/src/Darcs/Patch/V3/Core.hs... I even introduced operator symbols +| and -| as synonyms for some Data.Set operations in order to make the formulae more concise (and thus, IMHO, easier to read). It goes without saying that you cannot read non-trivial code like this as you read english prose. There is simply no way to understand it without having at least a rough idea of the underlying theoretical foundations. Cheers Ben

Ben, I think your proposition is righteous and uncontestable in theory, and I stand by you. Unfortunately the practice hardly aligns with the sermon. No one writes Mathematics in monospace ASCII left to right. They go to great lengths to actually type set things, generously use large and small font, bold and cursive, write above and below the line, use Greek and Hebrew and a myriad infix symbols. And for a reason — compare a latex source of a _«notation heavy»_ paper with it rendered. One may approach mathematical style in program source with generous use of Unicode, but few dare. Even type setting code in proportional font is considered heresy by many — just so that they may banish proper tabulation and _indent with spaces_. So, even the proponents of the mathematical style do not care to follow it as soon as it requires a little effort. _(Hoω h∀rd may it be to g∃t some ∪nic⊕de on one's kεyb∅arδ? See also the packages `base-unicode-symbols`[1] and `containers-unicode-symbols`[2].)_ Therefore I think for many it is merely an excuse for writing ugly code. The Darcs code you show illustrates the point Chris Done speaks for as well. Observe top level names: `displayPatch`, `commuteConflicting`, `cleanMerge` — quite German! Then there is `ctxAddInvFL` and `mapFL_FL`, but that from other modules. Finally, I tried to find out what `Prim` stands for — I went as far as to the index of `darcs` on Hackage[3] but no luck. And `prim` is the most frequent in the list of words of the module, with 125 occurrences in normalized case. Primitive? Primary? Prime? Primavera? [1]: https://hackage.haskell.org/package/base-unicode-symbols [2]: https://hackage.haskell.org/package/containers-unicode-symbols [3]: https://hackage.haskell.org/package/darcs-2.16.2/docs/doc-index-P.html

True, but it might have something to do with the fact that mathematics was invented long before monospaced fonts. And hand-writing integrals, or quantifiers, or the empty-set symbol, is just as easy as writing digits. I would rather agree with Ben: there are lots of places where long identifiers are distracting. Sometimes they make sense, but a lot of times they just don't.
On 20 Sep 2020, at 14:02, Ignat Insarov
wrote: Ben, I think your proposition is righteous and uncontestable in theory, and I stand by you. Unfortunately the practice hardly aligns with the sermon.
No one writes Mathematics in monospace ASCII left to right. They go to great lengths to actually type set things, generously use large and small font, bold and cursive, write above and below the line, use Greek and Hebrew and a myriad infix symbols. And for a reason — compare a latex source of a _«notation heavy»_ paper with it rendered.
One may approach mathematical style in program source with generous use of Unicode, but few dare. Even type setting code in proportional font is considered heresy by many — just so that they may banish proper tabulation and _indent with spaces_. So, even the proponents of the mathematical style do not care to follow it as soon as it requires a little effort. _(Hoω h∀rd may it be to g∃t some ∪nic⊕de on one's kεyb∅arδ? See also the packages `base-unicode-symbols`[1] and `containers-unicode-symbols`[2].)_ Therefore I think for many it is merely an excuse for writing ugly code.
The Darcs code you show illustrates the point Chris Done speaks for as well. Observe top level names: `displayPatch`, `commuteConflicting`, `cleanMerge` — quite German! Then there is `ctxAddInvFL` and `mapFL_FL`, but that from other modules. Finally, I tried to find out what `Prim` stands for — I went as far as to the index of `darcs` on Hackage[3] but no luck. And `prim` is the most frequent in the list of words of the module, with 125 occurrences in normalized case. Primitive? Primary? Prime? Primavera?
[1]: https://hackage.haskell.org/package/base-unicode-symbols [2]: https://hackage.haskell.org/package/containers-unicode-symbols [3]: https://hackage.haskell.org/package/darcs-2.16.2/docs/doc-index-P.html _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Am So., 20. Sept. 2020 um 14:20 Uhr schrieb MigMit
[...] there are lots of places where long identifiers are distracting. Sometimes they make sense, but a lot of times they just don't.
I think a good rule of thumb is: The length of an identifier should be proportional to the size of the scope in which it is valid. As an example: If you design an API, names like "openBinaryFile", "handleValidationError", "primaryDrawingContext" are a good idea. If you have a simple 1-line or 2-line helper function, one-letter names can make things vastly more readable, because you can see the "meat" of the code more easily without drowning in 20-letter identifiers spilled over 5 lines. So just using "ctx" or even "c" for "primaryDrawingContext" in a one-liner can improve things. This is even more true when you have a type annotation with long, descriptive type names for this function. But all of this is very subjective, and in the end writing good, readable code is a bit of an art. There are guidelines and tips on how to do this, but there can never be hard and fast rules which will make everybody happy.

Am 20.09.20 um 14:02 schrieb Ignat Insarov:
The Darcs code you show illustrates the point Chris Done speaks for as well. Observe top level names: `displayPatch`, `commuteConflicting`, `cleanMerge` — quite German!
Yes, top level functions are typical candidates for longer names. I am not opposed to the "german notation" in any way, I just don't think it is always appropriate to use this style for every variable, including function parameters, as suggested in the blog.
Then there is `ctxAddInvFL` and `mapFL_FL`, but that from other modules.
Well, sometimes you have to compromise between legibility and conciseness, especially when distinguishing between variants. The FL and RL sequence types are ubiquitous in our code base and the convention of suffixing a function with them to indicate what type of parameter it takes is well established. I wouldn't want to write out "monoidConcat" instead of "mconcat" everywhere. (Or would that have to be "semigroupConcat" nowadays? Thankfully we could avoid bikeshedding this to death...) Or "foldRight" or even "foldAssociatingRightwards" instead of "foldr".
Finally, I tried to find out what `Prim` stands for — I went as far as to the index of `darcs` on Hackage[3] but no luck. And `prim` is the most frequent in the list of words of the module, with 125 occurrences in normalized case. Primitive? Primary? Prime? Primavera?
Your first guess was correct ;-) Though I doubt that knowing this helps to understand the code better. Knowing that 'log' is short for 'logarithm' doesn't help you understand a formula containing 'log' unless you already know what 'logarithm' means. Long "german" names don't relieve you from the task of familiarizing yourself with the problem domain and its concepts and conventions. As regards type setting and unicode symbols, I am not a great fan of that stuff. IMO it makes no sense to mimic mathematical style in any literal sense. The point of a formula is not that it contains fancy special notation. Rather, the point is to avoid distracting the reader with irrelevant details. The only difference between a mathematical formula and a (functional) program is that the latter can be (efficiently) executed by a machine, *in addition* to being read and understood by humans. Besides, a lot of notational conventions in mathematics are not well suited to programming or formally proving things. Many (if not most) constructs that traditionally have special notation in math (e.g. sum, integral, etc) are subsumed by the concept of a higher order function. This has been well-known for several decades now, but the mathematical community is extremely conservative with its established notation. My personal explanation for this phenomenon is that all the existing work in math (books, papers) serve as a giant "standard library for the math language" and changing established notation would mean a huge effort in factorizing (i.e. re-writing) most of that existing work. That said, there are cases where a graphical notation is actually better suited for abstracting irrelevant details than the equivalent textual formula. The most well-known example for this is category theory with its arrow diagrams. As I found out a few years ago, patch theory is another instance where an arrow diagram is often more succinct and less cluttered than the textual formula. Ever since I wished I could include such diagrams directly in the code. Here is an example where I used ASCII graphics to explain a fairly complicated piece of code: https://hub.darcs.net/darcs/darcs-screened/browse/src/Darcs/Repository/Merge... This crutch clearly has limits: to picture a three-way merge you need to move from squares to cubes which gets quite annoying to do in ASCII. Cheers Ben

Well, sometimes you have to compromise between legibility and conciseness, especially when distinguishing between variants. The FL and RL sequence types are ubiquitous in our code base and the convention of suffixing a function with them to indicate what type of parameter it takes is well established. I wouldn't want to write out "monoidConcat" instead of "mconcat" everywhere. (Or would that have to be "semigroupConcat" nowadays? Thankfully we could avoid bikeshedding this to death...) Or "foldRight" or even "foldAssociatingRightwards" instead of "foldr".
My proposition is twofold and this is a perfect illustration for both its sides. 1. `mconcat` is an example of a thing that benefits from mathematical style. Please by all means shorten it to death and standardize. Take it from 7 symbols to 1 — best a beautiful pictogram. Same for `foldr`. > As regards type setting and unicode symbols, I am not a great fan of > that stuff. > > IMO it makes no sense to mimic mathematical style in any literal sense. > The point of a formula is not that it contains fancy special notation. It is not about what you think, it is about what you think others think. Quoting Leonardo Da Vinci: > It seems to me no small grace in a painter to be able to give a pleasing air > to his figures, and this grace, if he have it not by nature, he may acquire > it by incidental study in this way: Look about you and take the best parts > of many beautiful faces, of which the beauty is established rather by public > fame than by your own judgement; for you may deceive yourself and select > faces which bear a resemblance to your own, since it would often seem that > such resemblance pleases us; and if you were ugly you would select faces > that are not beautiful, and you would then create ugly faces as many > painters do. For often a master's shapes resemble himself; so therefore > select beauties as I tell you and fix them in your mind. That is, you should make sure that your judgement of beauty is independent of your own opinion. The effort of type setters and font designers is not vain. Even if you cannot detect the difference, you can guess that it is there by observing the choices of others. One famous programmer even went as far as to design a type setting language, I am sure you know his name. > Besides, a lot of notational conventions in mathematics are not well > suited to programming or formally proving things. Many (if not most) > constructs that traditionally have special notation in math (e.g. sum, > integral, etc) are subsumed by the concept of a higher order function. > This has been well-known for several decades now, but the mathematical > community is extremely conservative with its established notation. … I am sure the functional programming community deserves some special symbols of our own. I know research papers introduce various shorthand conventions for folds and such. Question is, whether we can find it in ourselves to converge on a notation. 2. `ctxAddInvFL` is an example of a thing that benefits from English prose style. I have a speech about it. There are things that are well established and at the same time not justifiable. As a special case, use may outlive justification. My proposition is that creative shortening was justified back then, but now is a relic. Benefits diminished, while drawbacks are still the same: * Harder to invent names. In addition to coming up with a short explanatory English phrase, you have to invent a plausible shortening — extra work. * Harder to read. As you see, it is virtually impossible to determine what `Prim` stands for, and that is an easy example. Even in a suggestive context, it is a tax on the mind of the reader. It is hard enough to learn English. * A trtr of lngstc snsblty. Try wrtn a blg pst ths way & see wht rdrshp u get. To continue from the previous point — it is hard enough to learn English, why should one be forced to learn an English to read prose and an Ngl to read code? I would rather not, if only out of æsthetic sense. I am sure one gets used to it. And I imagine it becomes faster to read and write the code in a given project once you internalize the shortenings. So then it is an optimization for those _«in»_ and a penalty for those _«out»_, thus setting up a _«walled garden»_. Is that ever wanted?

As a person who has been trying to learn Haskell for years I have a private
joke related to reading Haskell source which is “It has been x days since
I’ve seen completely unintelligible Haskell.” My sense is that language
extensions are a big part of this - they can have a significant impact on
readability and for a novice it is not at all clear how to differentiate
the text changes wrought by the extension. And in the presence of multiple
or even many extensions? Forget it.
So yes, I agree Haskell can be hard to read - and we haven’t even dredged
up the point/point-free debate!
With Kindness,
Brody
On Sat, Sep 19, 2020 at 08:33 Misja Alma
Thanks, these links are really useful! This definitely answers part of my question.
But what would still be really useful are some more or less generally accepted best practices about variable naming, indentation, when to use nested functions vs when to prefer keeping functions short, etc with regards to readability.
On Sat, 19 Sep 2020 at 17:10, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Sat, 19 Sep 2020, Misja Alma wrote:
Does anybody have any tips, or are there some sites or books that I
could read about this topic?
It may be a bit old but we have some articles on style in the Haskell
Wiki:
_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.

On Sat, Sep 19, 2020 at 05:02:41PM +0200, Misja Alma wrote:
I have been writing Haskell in my spare time for a couple of years now, but when I showed some code lately to a friend he remarked that he didn't find it very readable. Actually I agree, when I look at my own code of a couple of months old I have trouble figuring out too what exactly it is doing.
Could you perhaps show the code? Then I may be able to give suggestions about how to improve it. I have written a few articles about refactoring to improve readability it Haskell, for example: * http://h2.jaguarpaw.co.uk/posts/good-design-and-type-safety-in-yahtzee/ * http://h2.jaguarpaw.co.uk/posts/refactoring-neural-network/ Tom

My 2¢: my style comes from writing silly code and revisiting it and realizing what to do differently. I use stylish-haskell to order my import and I use hlint on my code. I think compared to other languages, one writes more small functions. And I rely more on haddock + type signatures - I've learned some ways to avoid writing bad haddocks by getting frustrated by packages on Hackage. Cheers, Vanessa McHale On 9/19/20 10:02 AM, Misja Alma wrote:
Hi,
I have been writing Haskell in my spare time for a couple of years now, but when I showed some code lately to a friend he remarked that he didn't find it very readable. Actually I agree, when I look at my own code of a couple of months old I have trouble figuring out too what exactly it is doing.
I'm coming from a Java and Scala background and there, especially for Java, are some generally accepted best practices that make sure that your teammates don't have too much trouble reading your code. E.g. write short functions with a single responsibility, use variable, class and function names that explain what they are meant for, etc.
I think some of those best practices, like short functions with single responsibility, are useful for Haskell as well. But Haskell is a different language than Java and has its own strong points and pitfalls regarding readability, so it probably needs different coding standards as well.
I have been looking on the Internet if I could find some tips about improving readability but all I could find was http://www.haskellforall.com/. Although there are some useful tips in there, this site seems to be aimed at making Haskell easier to read for newcomers from other languages. What I am interested in are tips from real projects that are built by real teams. Does anybody have any tips, or are there some sites or books that I could read about this topic?
Thanks, Misja
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

One important, sometimes difficult, part is to work out how to break up a
big function into multiple documentable small ones. Finding good natural
boundaries can be tough, and may require multiple attempts, but it's really
great when it works out. Ideally, each piece represents a single idea,
which makes independent sense without needing to know how it will be used.
Each piece should ideally have a small enough implementation to be able to
understand it easily, and should have a reasonably descriptive name.
On Sat, Sep 19, 2020, 11:03 AM Misja Alma
Hi,
I have been writing Haskell in my spare time for a couple of years now, but when I showed some code lately to a friend he remarked that he didn't find it very readable. Actually I agree, when I look at my own code of a couple of months old I have trouble figuring out too what exactly it is doing.
I'm coming from a Java and Scala background and there, especially for Java, are some generally accepted best practices that make sure that your teammates don't have too much trouble reading your code. E.g. write short functions with a single responsibility, use variable, class and function names that explain what they are meant for, etc.
I think some of those best practices, like short functions with single responsibility, are useful for Haskell as well. But Haskell is a different language than Java and has its own strong points and pitfalls regarding readability, so it probably needs different coding standards as well.
I have been looking on the Internet if I could find some tips about improving readability but all I could find was http://www.haskellforall.com/. Although there are some useful tips in there, this site seems to be aimed at making Haskell easier to read for newcomers from other languages. What I am interested in are tips from real projects that are built by real teams. Does anybody have any tips, or are there some sites or books that I could read about this topic?
Thanks, Misja
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

I'd like to understand this issue from the psychological aspect, that readable doesn't mean reasonable that much, while being readable well serves Illusion of control [1] of projects under management, for bosses in Bullshit Jobs[2], we actually need to be in flow state [3] to properly reason about (including reading) an important piece of code. It's not possible with just trivial effort or even in a hurry, even you wrote the code yourself, if not in resonance with the mindset behind the code. Within many (usually large) corporate codebase, you can easily read any small unit of code, so as to perceive that all of them are doing really useful things for each's own purpose, but very hard to discover how business goals can be fulfilled by the whole codebase. So long as business consultants and stakeholders don't speak a programming language, code in our PL won't express business logics directly. I had assumed the role of a translator between programmers and business users earlier in my career, i.e. doing requirement analysis & design implementation per ad-hoc basis, I would suggest that there are really big gaps. I love Haskell and I'd like to say, I don't expect Haskell code being easy to read, but for truly effective definitions of the problem and the solution, Haskell code should be really easier to reason about with the ultimate goal in mind. [1] https://en.wikipedia.org/wiki/Illusion_of_contro https://en.wikipedia.org/wiki/Illusion_of_control [2] https://en.wikipedia.org/wiki/Bullshit_Jobs https://en.wikipedia.org/wiki/Bullshit_Jobs [3] https://en.wikipedia.org/wiki/Flow_(psychology) https://en.wikipedia.org/wiki/Flow_(psychology) Compl
On 2020-09-19, at 23:02, Misja Alma
mailto:misja.alma@gmail.com> wrote: Hi,
I have been writing Haskell in my spare time for a couple of years now, but when I showed some code lately to a friend he remarked that he didn't find it very readable. Actually I agree, when I look at my own code of a couple of months old I have trouble figuring out too what exactly it is doing.
I'm coming from a Java and Scala background and there, especially for Java, are some generally accepted best practices that make sure that your teammates don't have too much trouble reading your code. E.g. write short functions with a single responsibility, use variable, class and function names that explain what they are meant for, etc.
I think some of those best practices, like short functions with single responsibility, are useful for Haskell as well. But Haskell is a different language than Java and has its own strong points and pitfalls regarding readability, so it probably needs different coding standards as well.
I have been looking on the Internet if I could find some tips about improving readability but all I could find was http://www.haskellforall.com/ http://www.haskellforall.com/. Although there are some useful tips in there, this site seems to be aimed at making Haskell easier to read for newcomers from other languages. What I am interested in are tips from real projects that are built by real teams. Does anybody have any tips, or are there some sites or books that I could read about this topic?
Thanks, Misja
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (15)
-
Ben Franksen
-
Branimir Maksimovic
-
Brody Berg
-
David Feuer
-
Henning Thielemann
-
Ignat Insarov
-
MarLinn
-
MigMit
-
Misja Alma
-
Oliver Charles
-
Sven Panne
-
Tom Ellis
-
Vanessa McHale
-
Viktor Dukhovni
-
YueCompl