Difference between revisions of "How to read Haskell"

From HaskellWiki
Jump to navigation Jump to search
(Tip for what: M _ ' l r mean as suffixes)
(Remove some needless discussiony stuff, promote all levels)
Line 1: Line 1:
This stub is intended to become a tutorial on reading Haskell. It's aimed at the non-Haskeller who probably doesn't care too much about trying to write code, but wants to understand it.
+
This (very incomplete) tutorial is aimed at the non-Haskeller who probably doesn't care too much about trying to write code, but wants to understand it.
 
Our adopted format is a collection of tips and tricks broken down by category. It probably isn't very important what order you read it in, but it might be good to start with the general advice. Please feel encouraged to make any complaints about Haskell on the discussion page! It will help us to improve this tutorial.
   
Note: you should also consider having a look at [[http://www.haskell.org/~pairwise/intro/intro.html Haskell for C Programmers]. It might be a good way to get over the culture shock.
+
Note: you should also consider having a look at [http://www.haskell.org/~pairwise/intro/intro.html Haskell for C Programmers]. It might be a good way to get over the culture shock.
   
== The tutorial ==
+
== General advice ==
   
 
=== Tip: it's just very very concise ===
This (very incomplete) tutorial consists of a collection of tips and tricks broken down by category. It probably isn't very important what order you read it in, but it might be good to start with the general advice. Please feel encouraged to make any complaints about Haskell on the discussion page! It will help us to improve this tutorial.
 
 
=== General advice ===
 
 
==== Tip: it's just very very concise ====
 
   
 
One thing that can make Haskell hard to read is that Haskell code is extremely succinct. One tiny little piece of code can say a lot, so many times, when you are faced with something you don't understand, the best thing you can do is to think about it for some time. It will usually make sense after a while. The good news is that because of this succinctness, Haskell functions tend to be very small, which means that when you're trying to understand a difficult piece of Haskell, you normally do not have to look very far. It's just two sides of the same coin:
 
One thing that can make Haskell hard to read is that Haskell code is extremely succinct. One tiny little piece of code can say a lot, so many times, when you are faced with something you don't understand, the best thing you can do is to think about it for some time. It will usually make sense after a while. The good news is that because of this succinctness, Haskell functions tend to be very small, which means that when you're trying to understand a difficult piece of Haskell, you normally do not have to look very far. It's just two sides of the same coin:
Line 17: Line 14:
 
Spending on this time to get one tiny line of code may be frustrating, but it's well worth the effort, because the fact that a very small code is hard to understand probably means that it's very abstract, and the fact that it is abstract probably means that it's going to be used in many places. So understanding that one tiny line code, as painful as it may have been initially, can pay off in a big way.
 
Spending on this time to get one tiny line of code may be frustrating, but it's well worth the effort, because the fact that a very small code is hard to understand probably means that it's very abstract, and the fact that it is abstract probably means that it's going to be used in many places. So understanding that one tiny line code, as painful as it may have been initially, can pay off in a big way.
   
==== Trick: use the haddock ====
+
=== Trick: use the haddock ===
   
 
When reading a long piece of Haskell code, one which is broken up into many modules, you should consider keeping a browser window open with the auto-generated API documentation on the side (if any).
 
When reading a long piece of Haskell code, one which is broken up into many modules, you should consider keeping a browser window open with the auto-generated API documentation on the side (if any).
   
=== What does this function do? ===
+
== What does this function do? ==
   
==== Trick: use type signatures ====
+
=== Trick: use type signatures ===
   
 
When you see stuff like this
 
When you see stuff like this
Line 34: Line 31:
 
:''elaborate''
 
:''elaborate''
   
==== Tip: Haskellers love pattern matching ====
+
=== Tip: Haskellers love pattern matching ===
   
 
:''elaborate''
 
:''elaborate''
   
==== Tip: a function may be defined in more than one piece ====
+
=== Tip: a function may be defined in more than one piece ===
   
 
Remember math class, where functions would be defined like abs(x) = x if x >= 0 or -x otherwise? It's a bit like that in Haskell too. Sometimes, rather than writing one big if-then-else, Haskellers find it more convenient to define a function separately for each case, such as...
 
Remember math class, where functions would be defined like abs(x) = x if x >= 0 or -x otherwise? It's a bit like that in Haskell too. Sometimes, rather than writing one big if-then-else, Haskellers find it more convenient to define a function separately for each case, such as...
Line 59: Line 56:
 
(Note: some programmers will perhaps write something like <code>foo x | otherwise = ...</code>. The <code>otherwise</code> is redundant (and equal to <code>True</code>), but useful as reminder that this isn't the entire definition of <code>foo</code>)
 
(Note: some programmers will perhaps write something like <code>foo x | otherwise = ...</code>. The <code>otherwise</code> is redundant (and equal to <code>True</code>), but useful as reminder that this isn't the entire definition of <code>foo</code>)
   
==== Tip: pattern matching and guards can be mixed and matched ====
+
=== Tip: pattern matching and guards can be mixed and matched ===
   
 
:''elaborate''
 
:''elaborate''
Line 70: Line 67:
 
</haskell>
 
</haskell>
   
=== What the heck is xyz? ===
+
== What the heck is xyz? ==
   
 
One problem you might face when reading Haskell code is figuring out some cryptic entity like <code>xyz</code> is.
 
One problem you might face when reading Haskell code is figuring out some cryptic entity like <code>xyz</code> is.
   
==== Tip: the smaller the name, the smaller the scope ====
+
=== Tip: the smaller the name, the smaller the scope ===
   
 
Do you hate the way Haskell code is littered with short, meaningless name like <code>x</code> and <code>xs</code>? When Haskell programmers use names like that, it's often for good reason.
 
Do you hate the way Haskell code is littered with short, meaningless name like <code>x</code> and <code>xs</code>? When Haskell programmers use names like that, it's often for good reason.
Line 80: Line 77:
 
:''elaborate: (1) scope size, (2) abstraction means it would be silly to give long names''
 
:''elaborate: (1) scope size, (2) abstraction means it would be silly to give long names''
   
==== Tip: the -s and m- habits ====
+
=== Tip: the -s and m- habits ===
   
 
There is a variable name habit that sometimes comes with short names. Typically, if you have a thing you want to name <code>x</code>, you'll sometimes want to name lists of these <code>xs</code>. As in the plural of <code>x</code>. So if you see a name like <code>as</code> or <code>bs</code> or <code>foos</code>, it's often good to mentally read that as "aeyes" (the plural of a), "bees" (the plural of b), and "foohs" (the plural of foo). It might seem obvious to some, but it took me a while to stop asking myself in situations like this, "<code>as</code>? What the heck is aey-ess?"
 
There is a variable name habit that sometimes comes with short names. Typically, if you have a thing you want to name <code>x</code>, you'll sometimes want to name lists of these <code>xs</code>. As in the plural of <code>x</code>. So if you see a name like <code>as</code> or <code>bs</code> or <code>foos</code>, it's often good to mentally read that as "aeyes" (the plural of a), "bees" (the plural of b), and "foohs" (the plural of foo). It might seem obvious to some, but it took me a while to stop asking myself in situations like this, "<code>as</code>? What the heck is aey-ess?"
Line 96: Line 93:
 
* foldl' - a fold that is strict in its accumulator, "'" is used to indicate a strict variant of a function
 
* foldl' - a fold that is strict in its accumulator, "'" is used to indicate a strict variant of a function
   
==== Tip: order doesn't matter ====
+
=== Tip: order doesn't matter ===
   
 
Outside of a monad, it really doesn't matter what order things in Haskell code appear. So if you see something like this...
 
Outside of a monad, it really doesn't matter what order things in Haskell code appear. So if you see something like this...
Line 107: Line 104:
 
:* ''except for monads? explain''
 
:* ''except for monads? explain''
   
==== Trick: use grep ====
+
=== Trick: use grep ===
   
 
(This might seem really obvious, but it's sometimes easy to forget)
 
(This might seem really obvious, but it's sometimes easy to forget)
Line 130: Line 127:
   
 
A fourth idea, if you can't find something, is to look it up in [http://haskell.org/hoogle/ Hoogle]
 
A fourth idea, if you can't find something, is to look it up in [http://haskell.org/hoogle/ Hoogle]
 
----
 
 
== What confuses non-Haskellers ==
 
 
Since this tutorial is not yet written, we encourage you to note here the things which confuse non-Haskellers about the code code.
 
 
* layout instead of semicolons?
 
* super-super-concise stuff (things using liftM and liftM2)
 
* the difference between <haskell>x <- foo</haskell> and <haskell>x = foo</haskell>
 
 
== Scratch pad ==
 
 
You have thirty seconds. Can you understand what <code>.+</code> does?
 
<haskell>
 
(-1) .+ _ = -1
 
_ .+ (-1) = -1
 
a .+ b = a + b
 
</haskell>
 
:I was initially going to use this example for saying that you should get used to pattern matching... but now I'm not so sure. It shows you two things really, (1) the pattern matching stuff, and (2) the fact that we like to define our operators in this infixy way.
 
   
 
[[Category:Tutorials]]
 
[[Category:Tutorials]]

Revision as of 04:20, 20 August 2006

This (very incomplete) tutorial is aimed at the non-Haskeller who probably doesn't care too much about trying to write code, but wants to understand it. Our adopted format is a collection of tips and tricks broken down by category. It probably isn't very important what order you read it in, but it might be good to start with the general advice. Please feel encouraged to make any complaints about Haskell on the discussion page! It will help us to improve this tutorial.

Note: you should also consider having a look at Haskell for C Programmers. It might be a good way to get over the culture shock.

General advice

Tip: it's just very very concise

One thing that can make Haskell hard to read is that Haskell code is extremely succinct. One tiny little piece of code can say a lot, so many times, when you are faced with something you don't understand, the best thing you can do is to think about it for some time. It will usually make sense after a while. The good news is that because of this succinctness, Haskell functions tend to be very small, which means that when you're trying to understand a difficult piece of Haskell, you normally do not have to look very far. It's just two sides of the same coin:

  • bad news: high density == spending more time per line of code
  • good news: succinctness == fewer lines of code to spend time on

Spending on this time to get one tiny line of code may be frustrating, but it's well worth the effort, because the fact that a very small code is hard to understand probably means that it's very abstract, and the fact that it is abstract probably means that it's going to be used in many places. So understanding that one tiny line code, as painful as it may have been initially, can pay off in a big way.

Trick: use the haddock

When reading a long piece of Haskell code, one which is broken up into many modules, you should consider keeping a browser window open with the auto-generated API documentation on the side (if any).

What does this function do?

Trick: use type signatures

When you see stuff like this

-- example please!
foo :: Bar Ping Pong -> Baz Zed Dubya -> IO (DoublePlus Good)

...don't fight it! These are type signatures and they are an incredibly useful way of getting a rough idea what a function is supposed to do.

elaborate

Tip: Haskellers love pattern matching

elaborate

Tip: a function may be defined in more than one piece

Remember math class, where functions would be defined like abs(x) = x if x >= 0 or -x otherwise? It's a bit like that in Haskell too. Sometimes, rather than writing one big if-then-else, Haskellers find it more convenient to define a function separately for each case, such as...

abs x | x >= 0 = x
abs x = -x

What gets confusing is when you look at a definition like this...

foo x | blah = 
 some enormous long thing

foo x =
 some other enourmously long thing

Especially looking at the bottom bit, it's hard to remember that foo might have a another definition lurking around. Luckily, you never have to look very far, either immediately above or immediately below the other definition.

(Note: some programmers will perhaps write something like foo x | otherwise = .... The otherwise is redundant (and equal to True), but useful as reminder that this isn't the entire definition of foo)

Tip: pattern matching and guards can be mixed and matched

elaborate
  combine ((f,a,b,r):(f',a',b',r'):ss)
    | f == f' = combine ((f,a.+a',b.+b',r+r'):ss)
  combine ((f,a,b,r):ss) = (f,a,b,r) : combine ss
  combine [] = []

What the heck is xyz?

One problem you might face when reading Haskell code is figuring out some cryptic entity like xyz is.

Tip: the smaller the name, the smaller the scope

Do you hate the way Haskell code is littered with short, meaningless name like x and xs? When Haskell programmers use names like that, it's often for good reason.

elaborate: (1) scope size, (2) abstraction means it would be silly to give long names

Tip: the -s and m- habits

There is a variable name habit that sometimes comes with short names. Typically, if you have a thing you want to name x, you'll sometimes want to name lists of these xs. As in the plural of x. So if you see a name like as or bs or foos, it's often good to mentally read that as "aeyes" (the plural of a), "bees" (the plural of b), and "foohs" (the plural of foo). It might seem obvious to some, but it took me a while to stop asking myself in situations like this, "as? What the heck is aey-ess?"

Similarly, another habit you might see is people who begin variable names with m-. This is probably less common, but if you see a lot of m-, it might be because of the Maybe type. Sometimes we have foo of type Whatever, and mfoo of type Maybe Whatever. Relax, this isn't Hungarian notation. It's not something that's used systematically, or rigidly in any way.

Both of these conventions are just helpful when you have both variants floating around in the same place, that is, when you have both Whatever and [Whatever] (that would be list of whatever), x and xs is a good way to indicate that they are both the same thing, except one comes in a list. Likewise, when you have both Whatever and Maybe Whatever in the same function, x and mx are too.

Finally, library functions are sometimes suffixed with "l", "r", "_", "M" or "'". What do these mean?

 * mapM    - the 'map' function lifted into a monad. An 'M' suffix implies that the function is a monadic version of an equivalent pure function 
 * mapM_   - the '_' suffix indicates that the result of this computation is discarded, and () is returned (by analogy with the _ pattern).
 * foldl   - a fold that traverses its structure left to right
 * foldr   - a fold that traverses its structure right to left
 * foldl'  - a fold that is strict in its accumulator, "'" is used to indicate a strict variant of a function

Tip: order doesn't matter

Outside of a monad, it really doesn't matter what order things in Haskell code appear. So if you see something like this...

foo = whatTheHeckIsBar

you should take into account that whatTheHeckIsBar may be defined somewhere below foo

  • scope in a nutshell
  • except for monads? explain

Trick: use grep

(This might seem really obvious, but it's sometimes easy to forget)

Or use the search feature of your favourite text editor. It's probably defined right there before your eyes, and if it's true to Haskell style, the definition is probably so small you blew right through it. In vi, for example, you could do /= *xyz which searches for =, an arbirtary number of spaces, and then xyz.

Barring that, xyz might be defined in some different module in the code you downloaded. You can look for telltale signs like

import Manamana (xyz)

But note that sometimes programmers get lazy, and they don't specify that xyz should be imported. They just let rip with

import Manamana

So solution number 3 would be do something like grep xyz *.lhs *.hs (Note that literate programs sometimes use non-literate code, so search in both lhs AND hs)

A fourth idea, if you can't find something, is to look it up in Hoogle