How to read Haskell

From HaskellWiki
Revision as of 12:11, 4 July 2007 by EricKow (talk | contribs)
Jump to navigation Jump to search

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

map :: (a -> b) -> [a] -> [b]

...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.

For example, the function above takes any function of type (a -> b) and yields a function that takes a list of a's and produces a list of b's. For example, sqrt takes a number and returns the square root of that number, so map sqrt takes a list of numbers and returns a list of their square roots.

As another example,

swap :: (a,b) -> (b,a)

This takes a tuple of (a,b) and gives back a tuple of type (b,a).

Here are some more things you might see in Haskell type signatures:

fn :: (b -> c) -> Foo -- fn is higher order; it takes a function from b -> c as input
fn :: x -> IO Int     -- fn is an input/output action that returns an Int
fn :: x -> [y]        -- fn returns a list of ys
fn :: x -> (y,z)      -- fn returns a tuple of (y,z)
fn :: x               -- fn is just a value

Tip: Haskellers love pattern matching

head [x] = x

This says that if 'head' is followed by a list containing only 1 item, label that item as 'x', and then return 'x'. Another example might be

fst (x,y) = x

snd (x,y) = y

These functions fetch the first and second items in a tuple, respectively. It should be fairly obvious how they work.

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 enormously 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.

First, typically, the short, "meaningless" names are contained within a very small space. Consider this typical (and inefficient!) implementation of a prime number generator:

primes :: [Integer]
primes = sieve [2..]
  where
    sieve (p:xs) = p : sieve [x|x <- xs, x `mod` p > 0]

The where block contains a function with strange variables like x and xs and p. In a more verbose language this could be difficult to read simply because it's difficult to actually find the definitions of small variables in long blocks of code. In C, for example, these would usually be defined at the top of a function which could have dozens (if not hundreds) of lines of code. Thus you might want to see p named as known_prime and xs named as candidate_primes or the like.

In this code, however, there is no such need for it. p is (implicitly) defined in the same line of code that uses it. xs, too, is defined there, as is x. Further all three variables use a popular naming convention which appends 's' to the names of lists (or equivalents) and uses single letters for singular values. The only unusual part is the selection of the pattern (p:xs) in the arguments over the more common (x:xs). Here the programmer is signalling (subtly) that this list head is somehow different from a normal list. Quick inspection demonstrates that p is guaranteed to be a prime number.

The reason coding can be expressed this way in Haskell without undue confusion is because of its extreme conciseness. The habits you've had to learn to manage more verbose languages simply don't apply anymore. It takes some getting used to, but it becomes a joy one you reach that point.

This, however, is not the main reason for such "meaningless" names. The real reason for such names is even deeper. The Haskell language allows for unparallelled levels of abstraction through functional composition and higher-order functions. Where in most imperative languages a "function" (or, more often, a procedure masquerading as a function) is a pretty low-level entity with very specific, tangible functionality, Haskell functions can be extremely abstract. Consider this canonical implementation of foldl from the Prelude:

foldl            :: (a -> b -> a) -> a -> [b] -> a
foldl f z []     = z
foldl f z (x:xs) = foldl f (f z x) xs

This function is a highly-abstract one. It is, in fact, an abstraction of iterating over a list and computing an aggregate result. What kind of list? Pretty much any kind. What kind of computation? Anything you'd care to name. What kind of result? Anything that matches the type of the priming value. What "meaningful" names can you apply to the variables here? Should it look something like this (elided and formed to fit a reasonable screen)?:

foldl binary_operation priming_value (list_head:list_body) = 
        foldl 
            binary_operation 
            (binary_operation priming_value list_head)
            list_body

Knowing a few simple conventions of Haskell variable naming (functions progress, typically, as f, g, etc. for example) makes the first, terse version far more readable as an abstract definition than does the second, verbose version—once you get used to it.

Tip: types, functions and values

Type variables in Haskell are typically named starting at a, b, etc. They are sometimes (but not often) decorated with numbers like a1 or b3.

Functions used as higher-order arguments are typically named starting at f, g, etc. They will sometimes be decorated with numbers like type variables and will also be decorated with the ' character like g'. You would read this latter example as "Jee-prime" and it is typically a function that is in some way related to g used as a helper or the like. Occasionally functions may be given names that are not on this continuum as an aide memoir, for example a function parameter used internally as a predicate may be given the name p.

Arguments to functions, or variables used exclusively inside short functions, are often given names starting at x, y, etc., again occasionally decorated by numbers. Other single-letter variable names may be chosen if they can act as a mnemonic for their role such as using a variable named p for a value known to be prime.

Note that these are guidelines and not rules. Any of them can and will be ignored, modified and/or abused in any given piece of Haskell code. (A quick look at the Standard Prelude as provided in the Haskell 98 Report should be convincing enough for this.)

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 mostly doesn't matter

It doesn't matter what order functions are defined in. This:

foo x y z = ...

bar a b = ... foo b ...

is exactly equivilent to this:

bar a b = ... foo b ...

foo x y z = ...

Functions further up can call functions that are defined lower down, and vice versa. Functions can be written in any order at all. It doesn't matter.

  • scope in a nutshell

Tip: order does matter for pieces of functions

Very important: whilst the order that you define individual functions does not matter, what does matter is the order that you define its individual pieces.

For example, these two versions of abs do NOT mean the same thing!

-- the right order
abs x | x >= 0 = x
abs x = -x

-- the wrong order
abs2 x = -x
abs2 x | x >= 0 = x

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

A fifth idea, for Hugs/WinHugs users, is to use the ":find" command, ":find xyz" will open up your text editor with the appropriate module, jumped to the correct place. GHCi users can use ":i xyz" to get the place "xyz" is defined. (It won't open an editor, though.)