Lecture 2: Lists

\[ \newcommand{\limplies}{\rightarrow} \]

Lists are an important and useful data structure in functional programming. Indeed, the name of the first widely used functional programming language, Lisp, is a portmanteau of “List Processing.”

In Haskell, a list is a sequence of objects of the same type. Often, we'll describe a list by an explicit enumeration of its elements, e.g.,

[1,2,3,4,5]

This is a nice notation, but it is important to understand that it is syntactic sugar, i.e., a clear and concise notation that reflects a commonly used pattern. For all it's considerable merits, this notation obscures the essential fact that there are only two kinds of lists:

More pedantically, the list above could be written as

1 : (2 : (3 : (4 : (5 : []))))

or more tersely (using the useful fact that (:) associates to the right) as

1:2:3:4:5:[]

Now, if you have any syntactic taste at all, you'll prefer the first form, [1,2,3,4,5] to the second and third forms. But this misses an important point—it is one thing to have a concise notation for lists, but if you want to write code that manipulates list structure, you have to understand how they're actually constructed.

Defining List Functions By Recursion

Let's start by implementing the standard length function:

-- | Functions for manipulating lists. module ListFunction where import Prelude hiding (length) -- | Count the number of elements in a list. length :: [a] -> Int length [] = 0 length (c:cs) = 1 + length cs

There's a fair bit going on here! A first thing to note is that length is a predefined function, and Haskell's not happy if the same name has two definitions. We avoid this problem by an import of the Prelude which hides the definition of length. This isn't all that common in practice, but it crops up a lot with list-based functions and introductions to Haskell. Note that the length function in the Prelude has a different (and more general) type.

Note the type declaration. The length function that takes as arguments a list (over an arbitrary base type a), and returns the number of elements it contains. This is a polymorphic definition, and the resulting function can be applied to lists over any type. We've not seen the Int type before, but it is just a finite precision (usually 64-bit, these days) integer. In this case, we don't need a constraint on a, because we're not going to do anything that depends on the elements of the function.

The definition above is based on pattern matching. Instead of naming the arguments to a function via a variable, as we've done before, the argument positions are inhabited by patterns, which either match or fail to match. Each of the clauses of a pattern matching definition are considered in order, and the equation corresponding to the first matching pattern is used.

This definition is also a natural recursion on list structure, i.e.,

Let's take the definition of length apart, piece by piece

length [] = ... length (c:cs) = ...

The parentheses around the cons (:) in the second line are not optional. Function application binds more tightly than infix operations in Haskell, and so, without the parentheses, it would interpret length c:cs as (length c):cs, and interpret your equation as an attempt to define (:)!

In the first case, our pattern matches only the empty list [], which contains no elements, so we can define the result directly:

length [] = 0

In the second case, the pattern matches a (:), and so we're dealing with a list that adds an element onto the front of another list. We can use a recursive call to account for the length of that sublist:

length (c:cs) = ... length cs

and we can use this result to compute the length of the original list, which has precisely one element more:

length (c:cs) = 1 + length cs

Finally, an experienced Haskell programmer would make one further change. Portions of a pattern that we don't need can be matched using just an underscore _, thus,

length [] = 0 length (_:cs) = 1 + length cs

This idiom allows us to focus on the parts of the pattern that are important in reducing an expression.

We can use the same approach in defining the sum function, which adds up the elements of a list.

-- | Compute the sum of the numbers in a list. sum :: Num n => [n] -> n sum [] = 0 sum (x:xs) = x + sum xs

In this case, the Num constraint is necessary because of our use of (+).

Let's consider a slightly different problem—summing the squares of the elements of a list. We're going to consider this simple problem from several angles.

A first approach would be a direct implementation, like this:

-- | Compute the sum of the squares of the numbers in a list. sumSquares :: Num n => [n] -> n sumSquares [] = 0 sumSquares (x:xs) = x^2 + sumSquares xs

You will soon be able to write definitions like this pretty quickly, e.g., a sum of cubes function might be written like this:

-- | Compute the sum of the cubes of the numbers in a list. sumCubes :: Num n => [n] -> n sumCubes [] = 0 sumCubes (x:xs) = x^3 + sumCubes xs

Higher Order List Functions

As natural as this is, and as comfortable as it becomes, experienced programmers want to avoid writing the same code over and over again—so this will inspire them to find appropriate abstractions that capture the relevant commonalities, and then to express the particular versions as special cases.

For example, we might abstract away that we're summing functions applied to elements of a list. This gives rise to a definitions like this:

-- | Given a function f, compute the sum of the images under f of the elements of a list sumf :: Num n => (a -> n) -> [a] -> n sumf f [] = 0 sumf f (c:cs) = f c + sumf f cs -- | Square a number square :: Num n => n -> n square x = x^2 -- | Compute the third power of a number cube :: Num n => n -> n cube x = x^3 -- | Compute the sum of the squares of the numbers in a list. sumSquares :: Num n => [n] -> n sumSquares xs = sumf square xs -- | Compute the sum of the cubes of the numbers in a list. sumCubes :: Num n => [n] -> n sumCubes xs = sumf cube xs

Although the second implementation of sumSquares is a bit longer (four lines vs. two), this second version is to be preferred because it achieves a clean factoring of the problem into a recursive summing part, and a function computing part, which makes it easier to build functions that sum other things, whereas in the first version, these aspects are intertwined. Moreover, we've only started with the second version, and there is room for improvement.

One objection to the code above is that we've had to add top-level definitions of the square and cube functions, even though they're not something that we're interested in directly. Of course, at this point, we only know how to do top level definitions! We can simplify this conceptually by adding using local definitions of square and cube where needed:

-- | Compute the sum of the squares of the numbers in a list. sumSquares :: Num n => [n] -> n sumSquares xs = sumf square xs where square x = x^2 -- | Compute the sum of the cubes of the numbers in a list. sumCubes :: Num n => [n] -> n sumCubes xs = sumf cubes xs where cube x = x^3

We can include many definitions within a single where clause, but they all have to indented (and by the same amount) relative to the higher-level clause in which they occur. An alternative to where is let:

-- | Compute the sum of the squares of the numbers in a list. sumSquares :: Num n => [n] -> n sumSquares xs = let square x = x^2 in sumf square xs -- | Compute the sum of the cubes of the numbers in a list. sumCubes :: Num n => [n] -> n sumCubes xs = let cube x = x^3 in sumf cubes xs

The difference between let and where is more subtle than whether the definitions come first or last. The let construct is part of the expression syntax of Haskell, whereas the where construct is part of the definition syntax.

*Exercise 2.1 Consider the expression sumf (sumf square) [[1,2],[3,4]]. Do a step-by-step substitution-based evaluation of this expression (you may omit trivial steps, e.g., square 4 => 16 is permitted).

But, as they say on late-night commercials, we're not done yet!

Let's factor the problem somewhat differently. In the current implementation, the process of building the sum and evaluating the function remain intertwined, even as we've abstracted out the particular function being evaluated. They can be separated. To that end, let's consider the map function, which might be implemented as follows:

-- | Map a function across a list. map :: (a -> b) -> [a] -> [b] map f [] = [] map f (x:xs) = f x : map f xs

This is another natural recursion, which builds a new list, gathering into a list the image under the given function of each of the elements of the original list. For example

> map square [1..4] [1,4,9,16]

Note also another Haskellism for constructing a list. Certainly, writing [1..1000] is a lot easier than writing out the list long hand, but it's also, and more importantly, clearer and less error prone.

With map in hand, we can write

sumSquares xs = sum (map square xs)

This is literally a one-liner (assuming we've defined square), because sum and map are predefined in Prelude.hs, and it's superfluous to code them ourselves. It may not be clear that we've gained anything, but we're not done yet. Haskell programmers like to manipulate their code, applying meaning-preserving transformations that result in code that more concise and more flexible.

One such tranformation is η-reduction. (The glyph ‘η’ is the Greek letter “eta.”) The way this works is that if we have a definition of the form

f x = N x

where N is an expression not containing x, we can cancel the x from both sides, and write

f = N

The mathematical idea underlying $\eta$-reduction is the principle of extensionality, the idea that two functions are equal if they have the same domain, and have the same value at every point of that domain, \begin{equation*} (\forall x. \; f(x) = g(x)) \limplies f = g. \end{equation*}

Returning now to our earlier definition, we have

sumSquares xs = sum (map square xs)

This doesn't take the form we need for η-reduction, but it's close: there's only one occurrence of xs on the right-hand side of the definition, and it comes at the end (albeit embedded within essential parentheses).

Haskell is actually a curried language, in which all functions are unary. Thus, a function like map, formally takes a single argument (e.g., square in the example above), which returns a unary function. In Haskell, application associates to the left, so the right hand side of this is actually

sum ((map square) xs)

The pattern f (g x) appears a lot in functional code, so naturally enough there's an operator (.), called composition such that f (g x) == (f . g) x. We can use this to re-write the definition above as

sumSquares xs = (sum . map square) xs

and η-reduce to

sumSquares = sum . map square

which is pretty tight. But was this all worth the effort? For a programmer, this is going to boil down to clarity, efficiency, and maintainability. This may not seem too clear to you just yet, but it will grow on you. You can think about a succession of functions that get applied to a list, read right-to-left, possibly including a summarization function (like sum) at the end. And it's very easy to think about changing the parts or order, e.g., altering the summarization function so that a sum is replaced by a product.

This style of programming is sometimes called “point-free,” we don't name the “point” in the domain to define the function. Instead, we use function combinators.

*Exercise 2.2. Implement the product function. This should take a list of numbers, and return their product. Unsurprisingly, product is defined in the Prelude, which creates a conflict. You can avoid this by using a hiding clause as above.

Use your implementation of product to determine the product of the squares of the first numbers 1 through 10.

Let's suppose now that we wanted to sum the squares of the odd numbers from one to one-hundred. This involves a new programming construct, guarded equations:

-- | Compute the sum of squares of the odd integers in a list sumSquaresOfOdds :: Integral n => [n] -> n sumSquaresOfOdds [] = 0 sumSquaresOfOdds (x:xs) | odd x = x^2 + sumSquaresOfOdds xs | otherwise = sumSquaresOfOdds xs

This captures a different sort of definition by cases: patterns consider the structure of the arguments to a function, guards consider the values of those constituents. Note that patterns can introduce new bindings, whereas guards do not. The evaluation of a block of guarded equations works much like the evaluation of a block of pattern-based equations: each guard is considered in turn, and the equation associated with the first true guard is used.

After our discussion of map, perhaps you can anticipate the next step. Here we're actually mixing together three distinct things: filtering a list for elements that meet a particular test, squaring each resulting element, and combining the results via sum. In this case, the filtering is the new part:

-- | Return a sublist comprised of the elements of a list that satisfies a predicate. filter :: (a -> Bool) -> [a] -> [a] filter p [] = [] filter p (x:xs) | p x = x : filter p xs | otherwise = filter p xs

Note that the Bool type consists of values that can be True or False. Again, filter is a built-in function in the Prelude, so we don't actually need to implement it. But after our experience from simplifying sumSquares, the final form of our solution practically writes itself:

sumSquaresOfOdds = sum . map square . filter odd

*Exercise 2.3 Let's consider the following problem: compute the sum of the first 100 natural numbers which are divisible by 2 and 3, but not 4 or 9. We'd like to do this in a way that makes it easy to perform similar computations in the future.

It's not hard to see that we're going to need to use sum and filter. There's a very nice function in the Prelude named take, which will return the first n elements of a list. With this, the problem boils down to

result = sum . take 100 . ?? $ [0..]

There's some new syntax here:

How can we fill in the ??? First off, it would be nice to have a predicate divisibleBy such that divisibleBy d n evaluates to True if and only if d evenly divides n. With such a predicate, we could solve the problem this way:

result = sum . take 100 . filter (divisibleBy 2) . filter (divisibleBy 3) . filter (not . divisibleBy 4) . filter (not . divisibleBy 9) $ [0..]

This isn't terrible, but it feels just a bit cumbersome. It would be nice to have a function allp which takes two arguments, a list of predicates ps, and a value x, and which returns True if and only if p x evaluates to True for every p in ps. With this, we could write:

result2 = sum . take 100 . filter (allp [ divisibleBy 2 , divisibleBy 3 , not . divisibleBy 4 , not . divisibleBy 9 ]) $ [0..]

This feels a lot better, because it is fairly easy for us to insert or delete tests. But we can due just a bit better still, writing another function filterAll that combines filter with allp, so that

result3 = sum . take 100 . filterAll [ divisibleBy 2 , divisibleBy 3 , not . divisibleBy 4 , not . divisibleBy 9 ] $ [0..]

For this exercise, you should define

And verify that all three results are the same. Strive for simplicity and clarity in your code.

There's something quite deep happening with Exercise 2.3, in that this code produces a result in finitely much time, even though some of the subexpressions (consider [0..]) describe infinite lists. The key feature of Haskell that makes this possible is laziness: we don't need to build all of these infinite lists, just enough so that the first 100 elements of the top-level list are defined. So that's all the evaluation that Haskell does!

Exercise 2.4 The definition of allp you gave for the previous exercise was probably a recursive definition in the style of the definition of map or filter. If you think about the problem a bit, you'll see that you the definition can be reduced to mapping application of a list of functions to a given point with a function that takes a list of booleans, and returns True if and only if all of the elements of that list are True. The later function already exists in the Prelude, as and. This means that you can define allp without an explicitly recursive definition, all you need to do is come up with a function that evaluates another function at a given point.

Give such a definition of allp.