Lists and Patterns - Language Concepts - Real World OCaml (2013)

Real World OCaml (2013)

Part I. Language Concepts

Chapter 3. Lists and Patterns

This chapter will focus on two common elements of programming in OCaml: lists and pattern matching. Both of these were discussed in Chapter 1, but we’ll go into more depth here, presenting the two topics together and using one to help illustrate the other.

List Basics

An OCaml list is an immutable, finite sequence of elements of the same type. As we’ve seen, OCaml lists can be generated using a bracket-and-semicolon notation:

OCaml utop

# [1;2;3];;

- : int list = [1; 2; 3]

And they can also be generated using the equivalent :: notation:

OCaml utop (part 1)

# 1 :: (2 :: (3 :: [])) ;;

- : int list = [1; 2; 3]

# 1 :: 2 :: 3 :: [] ;;

- : int list = [1; 2; 3]

As you can see, the :: operator is right-associative, which means that we can build up lists without parentheses. The empty list [] is used to terminate a list. Note that the empty list is polymorphic, meaning it can be used with elements of any type, as you can see here:

OCaml utop (part 2)

# letempty = [];;

val empty : 'a list = []

# 3 :: empty;;

- : int list = [3]

# "three" :: empty;;

- : string list = ["three"]

The way in which the :: operator attaches elements to the front of a list reflects the fact that OCaml’s lists are in fact singly linked lists. The figure below is a rough graphical representation of how the list 1 :: 2 :: 3 :: [] is laid out as a data structure. The final arrow (from the box containing 3) points to the empty list.

Diagram

image with no caption

Each :: essentially adds a new block to the proceding picture. Such a block contains two things: a reference to the data in that list element, and a reference to the remainder of the list. This is why :: can extend a list without modifying it; extension allocates a new list element but change any of the existing ones, as you can see:

OCaml utop (part 3)

# letl = 1 :: 2 :: 3 :: [];;

val l : int list = [1; 2; 3]

# letm = 0 :: l;;

val m : int list = [0; 1; 2; 3]

# l;;

- : int list = [1; 2; 3]

Using Patterns to Extract Data from a List

We can read data out of a list using a match statement. Here’s a simple example of a recursive function that computes the sum of all elements of a list:

OCaml utop (part 4)

# letrecsuml =

matchlwith

| [] -> 0

| hd :: tl -> hd + sumtl

;;

val sum : int list -> int = <fun>

# sum [1;2;3];;

- : int = 6

# sum[];;

- : int = 0

This code follows the convention of using hd to represent the first element (or head) of the list, and tl to represent the remainder (or tail).

The match statement in sum is really doing two things: first, it’s acting as a case-analysis tool, breaking down the possibilities into a pattern-indexed list of cases. Second, it lets you name substructures within the data structure being matched. In this case, the variables hd and tl are bound by the pattern that defines the second case of the match statement. Variables that are bound in this way can be used in the expression to the right of the arrow for the pattern in question.

The fact that match statements can be used to bind new variables can be a source of confusion. To see how, imagine we wanted to write a function that filtered out from a list all elements equal to a particular value. You might be tempted to write that code as follows, but when you do, the compiler will immediately warn you that something is wrong:

OCaml utop (part 5)

# letrecdrop_valuelto_drop =

matchlwith

| [] -> []

| to_drop :: tl -> drop_valuetlto_drop

| hd :: tl -> hd :: drop_valuetlto_drop

;;

Characters 114-122:

Warning 11: this match case is unused.

val drop_value : 'a list -> 'a -> 'a list = <fun>

Moreover, the function clearly does the wrong thing, filtering out all elements of the list rather than just those equal to the provided value, as you can see here:

OCaml utop (part 6)

# drop_value [1;2;3] 2;;

- : int list = []

So, what’s going on?

The key observation is that the appearance of to_drop in the second case doesn’t imply a check that the first element is equal to the value to_drop passed in as an argument to drop_value. Instead, it just causes a new variable to_drop to be bound to whatever happens to be in the first element of the list, shadowing the earlier definition of to_drop. The third case is unused because it is essentially the same pattern as we had in the second case.

A better way to write this code is not to use pattern matching for determining whether the first element is equal to to_drop, but to instead use an ordinary if statement:

OCaml utop (part 7)

# letrecdrop_valuelto_drop =

matchlwith

| [] -> []

| hd :: tl ->

letnew_tl = drop_valuetlto_dropin

ifhd = to_dropthennew_tlelsehd :: new_tl

;;

val drop_value : 'a list -> 'a -> 'a list = <fun>

# drop_value [1;2;3] 2;;

- : int list = [1; 3]

Note that if we wanted to drop a particular literal value (rather than a value that was passed in), we could do this using something like our original implementation of drop_value:

OCaml utop (part 8)

# letrecdrop_zerol =

matchlwith

| [] -> []

| 0 :: tl -> drop_zerotl

| hd :: tl -> hd :: drop_zerotl

;;

val drop_zero : int list -> int list = <fun>

# drop_zero [1;2;0;3];;

- : int list = [1; 2; 3]

Limitations (and Blessings) of Pattern Matching

The preceding example highlights an important fact about patterns, which is that they can’t be used to express arbitrary conditions. Patterns can characterize the layout of a data structure and can even include literals, as in the drop_zero example, but that’s where they stop. A pattern can check if a list has two elements, but it can’t check if the first two elements are equal to each other.

You can think of patterns as a specialized sublanguage that can express a limited (though still quite rich) set of conditions. The fact that the pattern language is limited turns out to be a very good thing, making it possible to build better support for patterns in the compiler. In particular, both the efficiency of match statements and the ability of the compiler to detect errors in matches depend on the constrained nature of patterns.

Performance

Naively, you might think that it would be necessary to check each case in a match in sequence to figure out which one fires. If the cases of a match were guarded by arbitrary code, that would be the case. But OCaml is often able to generate machine code that jumps directly to the matched case based on an efficiently chosen set of runtime checks.

As an example, consider the following rather silly functions for incrementing an integer by one. The first is implemented with a match statement, and the second with a sequence of if statements:

OCaml utop (part 9)

# letplus_one_matchx =

matchxwith

| 0 -> 1

| 1 -> 2

| 2 -> 3

| _ -> x + 1

letplus_one_ifx =

if x = 0then1

elseifx = 1then2

elseifx = 2then3

elsex + 1

;;

val plus_one_match : int -> int = <fun>

val plus_one_if : int -> int = <fun>

Note the use of _ in the above match. This is a wildcard pattern that matches any value, but without binding a variable name to the value in question.

If you benchmark these functions, you’ll see that plus_one_if is considerably slower than plus_one_match, and the advantage gets larger as the number of cases increases. Here, we’ll benchmark these functions using the core_bench library, which can be installed by running opam install core_bench from the command line:

OCaml utop (part 10)

# #require"core_bench";;

# openCore_bench.Std;;

# letrun_benchtests =

Bench.bench

~ascii_table:true

~display:Textutils.Ascii_table.Display.column_titles

tests

;;

val run_bench : Bench.Test.t list -> unit = <fun>

# [ Bench.Test.create ~name:"plus_one_match" (fun() ->

ignore (plus_one_match10))

; Bench.Test.create ~name:"plus_one_if" (fun() ->

ignore (plus_one_if10)) ]

|> run_bench

;;

Estimated testing time 20s (change using -quota SECS).

Name Time (ns) % of max

---------------- ----------- ----------

plus_one_match 46.81 68.21

plus_one_if 68.63 100.00

- : unit = ()

Here’s another, less artificial example. We can rewrite the sum function we described earlier in the chapter using an if statement rather than a match. We can then use the functions is_empty, hd_exn, and tl_exn from the List module to deconstruct the list, allowing us to implement the entire function without pattern matching:

OCaml utop (part 11)

# letrecsum_ifl =

ifList.is_emptylthen0

elseList.hd_exnl + sum_if (List.tl_exnl)

;;

val sum_if : int list -> int = <fun>

Again, we can benchmark these to see the difference:

OCaml utop (part 12)

# letnumbers = List.range01000in

[ Bench.Test.create ~name:"sum_if" (fun() -> ignore (sum_ifnumbers))

; Bench.Test.create ~name:"sum" (fun() -> ignore (sumnumbers)) ]

|> run_bench

;;

Estimated testing time 20s (change using -quota SECS).

Name Time (ns) % of max

-------- ----------- ----------

sum_if 110_535 100.00

sum 22_361 20.23

- : unit = ()

In this case, the match-based implementation is many times faster than the if-based implementation. The difference comes because we need to effectively do the same work multiple times, since each function we call has to reexamine the first element of the list to determine whether or not it’s the empty cell. With a match statement, this work happens exactly once per list element.

Generally, pattern matching is more efficient than the alternatives you might code by hand. One notable exception is matches over strings, which are in fact tested sequentially, so matches containing a long sequence of strings can be outperformed by a hash table. But most of the time, pattern matching is a clear performance win.

Detecting Errors

The error-detecting capabilities of match statements are if anything more important than their performance. We’ve already seen one example of OCaml’s ability to find problems in a pattern match: in our broken implementation of drop_value, OCaml warned us that the final case was redundant. There are no algorithms for determining if a predicate written in a general-purpose language is redundant, but it can be solved reliably in the context of patterns.

OCaml also checks match statements for exhaustiveness. Consider what happens if we modify drop_zero by deleting the handler for one of the cases. As you can see, the compiler will produce a warning that we’ve missed a case, along with an example of an unmatched pattern:

OCaml utop (part 13)

# letrecdrop_zerol =

matchlwith

| [] -> []

| 0 :: tl -> drop_zerotl

;;

Characters 26-84:

Warning 8: this pattern-matching is not exhaustive.

Here is an example of a value that is not matched:

1::_

val drop_zero : int list -> 'a list = <fun>

Even for simple examples like this, exhaustiveness checks are pretty useful. But as we’ll see in Chapter 6, they become yet more valuable as you get to more complicated examples, especially those involving user-defined types. In addition to catching outright errors, they act as a sort of refactoring tool, guiding you to the locations where you need to adapt your code to deal with changing types.

Using the List Module Effectively

We’ve so far written a fair amount of list-munging code using pattern matching and recursive functions. But in real life, you’re usually better off using the List module, which is full of reusable functions that abstract out common patterns for computing with lists.

Let’s work through a concrete example to see this in action. We’ll write a function render_table that, given a list of column headers and a list of rows, prints them out in a well-formatted text table, as follows:

OCaml utop (part 69)

# printf"%s\n"

(render_table

["language";"architect";"first release"]

[ ["Lisp" ;"John McCarthy" ;"1958"] ;

["C" ;"Dennis Ritchie";"1969"] ;

["ML" ;"Robin Milner" ;"1973"] ;

["OCaml";"Xavier Leroy" ;"1996"] ;

]);;

| language | architect | first release |

|----------+----------------+---------------|

| Lisp | John McCarthy | 1958 |

| C | Dennis Ritchie | 1969 |

| ML | Robin Milner | 1973 |

| OCaml | Xavier Leroy | 1996 |

- : unit = ()

The first step is to write a function to compute the maximum width of each column of data. We can do this by converting the header and each row into a list of integer lengths, and then taking the element-wise max of those lists of lengths. Writing the code for all of this directly would be a bit of a chore, but we can do it quite concisely by making use of three functions from the List module: map, map2_exn, and fold.

List.map is the simplest to explain. It takes a list and a function for transforming elements of that list, and returns a new list with the transformed elements. Thus, we can write:

OCaml utop (part 14)

# List.map ~f:String.length ["Hello"; "World!"];;

- : int list = [5; 6]

List.map2_exn is similar to List.map, except that it takes two lists and a function for combining them. Thus, we might write:

OCaml utop (part 15)

# List.map2_exn ~f:Int.max [1;2;3] [3;2;1];;

- : int list = [3; 2; 3]

The _exn is there because the function throws an exception if the lists are of mismatched length:

OCaml utop (part 16)

# List.map2_exn ~f:Int.max [1;2;3] [3;2;1;0];;

Exception: (Invalid_argument "length mismatch in rev_map2_exn: 3 <> 4 ").

List.fold is the most complicated of the three, taking three arguments: a list to process, an initial accumulator value, and a function for updating the accumulator. List.fold walks over the list from left to right, updating the accumulator at each step and returning the final value of the accumulator when it’s done. You can see some of this by looking at the type-signature for fold:

OCaml utop (part 17)

# List.fold;;

- : 'a list -> init:'accum -> f:('accum -> 'a -> 'accum) -> 'accum = <fun>

We can use List.fold for something as simple as summing up a list:

OCaml utop (part 18)

# List.fold ~init:0 ~f:(+) [1;2;3;4];;

- : int = 10

This example is particularly simple because the accumulator and the list elements are of the same type. But fold is not limited to such cases. We can for example use fold to reverse a list, in which case the accumulator is itself a list:

OCaml utop (part 19)

# List.fold ~init:[] ~f:(funlistx -> x :: list) [1;2;3;4];;

- : int list = [4; 3; 2; 1]

Let’s bring our three functions together to compute the maximum column widths:

OCaml utop (part 20)

# letmax_widthsheaderrows =

letlengthsl = List.map ~f:String.lengthlin

List.foldrows

~init:(lengthsheader)

~f:(funaccrow ->

List.map2_exn ~f:Int.maxacc (lengthsrow))

;;

val max_widths : string list -> string list list -> int list = <fun>

Using List.map we define the function lengths, which converts a list of strings to a list of integer lengths. List.fold is then used to iterate over the rows, using map2_exn to take the max of the accumulator with the lengths of the strings in each row of the table, with the accumulator initialized to the lengths of the header row.

Now that we know how to compute column widths, we can write the code to generate the line that separates the header from the rest of the text table. We’ll do this in part by mapping String.make over the lengths of the columns to generate a string of dashes of the appropriate length. We’ll then join these sequences of dashes together using String.concat, which concatenates a list of strings with an optional separator string, and ^, which is a pairwise string concatenation function, to add the delimiters on the outside:

OCaml utop (part 21)

# letrender_separatorwidths =

letpieces = List.mapwidths

~f:(funw -> String.make (w + 2) '-')

in

"|" ^ String.concat ~sep:"+"pieces ^ "|"

;;

val render_separator : int list -> string = <fun>

# render_separator [3;6;2];;

- : string = "|-----+--------+----|"

Note that we make the line of dashes two larger than the provided width to provide some whitespace around each entry in the table.

PERFORMANCE OF STRING.CONCAT AND ^

In the preceding code we’ve concatenated strings two different ways: String.concat, which operates on lists of strings; and ^, which is a pairwise operator. You should avoid ^ for joining long numbers of strings, since it allocates a new string every time it runs. Thus, the following code

OCaml utop (part 22)

# lets = "." ^ "." ^ "." ^ "." ^ "." ^ "." ^ ".";;

val s : string = "......."

will allocate strings of length 2, 3, 4, 5, 6 and 7, whereas this code

OCaml utop (part 23)

# lets = String.concat [".";".";".";".";".";".";"."];;

val s : string = "......."

allocates one string of size 7, as well as a list of length 7. At these small sizes, the differences don’t amount to much, but for assembling large strings, it can be a serious performance issue.

Now we need code for rendering a row with data in it. We’ll first write a function called pad, for padding out a string to a specified length plus one blank space on both sides:

OCaml utop (part 24)

# letpadslength =

" " ^ s ^ String.make (length - String.lengths + 1) ' '

;;

val pad : string -> int -> string = <fun>

# pad"hello"10;;

- : string = " hello "

We can render a row of data by merging together the padded strings. Again, we’ll use List.map2_exn for combining the list of data in the row with the list of widths:

OCaml utop (part 25)

# letrender_rowrowwidths =

letpadded = List.map2_exnrowwidths ~f:padin

"|" ^ String.concat ~sep:"|"padded ^ "|"

;;

val render_row : string list -> int list -> string = <fun>

# render_row ["Hello";"World"] [10;15];;

- : string = "| Hello | World |"

Now we can bring this all together in a single function that renders the table:

OCaml utop (part 26)

# letrender_tableheaderrows =

letwidths = max_widthsheaderrowsin

String.concat ~sep:"\n"

(render_rowheaderwidths

:: render_separatorwidths

:: List.maprows ~f:(funrow -> render_rowrowwidths)

)

;;

val render_table : string list -> string list list -> string = <fun>

More Useful List Functions

The previous example we worked through touched on only three of the functions in List. We won’t cover the entire interface (for that you should look at the online docs), but a few more functions are useful enough to mention here.

Combining list elements with List.reduce

List.fold, which we described earlier, is a very general and powerful function. Sometimes, however, you want something simpler and easier to use. One such function is List.reduce, which is essentially a specialized version of List.fold that doesn’t require an explicit starting value, and whose accumulator has to consume and produce values of the same type as the elements of the list it applies to.

Here’s the type signature:

OCaml utop (part 27)

# List.reduce;;

- : 'a list -> f:('a -> 'a -> 'a) -> 'a option = <fun>

reduce returns an optional result, returning None when the input list is empty.

Now we can see reduce in action:

OCaml utop (part 28)

# List.reduce ~f:(+) [1;2;3;4;5];;

- : int option = Some 15

# List.reduce ~f:(+) [];;

- : int option = None

Filtering with List.filter and List.filter_map

Very often when processing lists, you wants to restrict your attention to a subset of the values on your list. The List.filter function is one way of doing that:

OCaml utop (part 29)

# List.filter ~f:(funx -> x mod 2 = 0) [1;2;3;4;5];;

- : int list = [2; 4]

Note that the mod used above is an infix operator, as described in Chapter 2.

Sometimes, you want to both transform and filter as part of the same computation. In that case, List.filter_map is what you need. The function passed to List.filter_map returns an optional value, and List.filter_map drops all elements for which None is returned.

Here’s an example. The following expression computes the list of file extensions in the current directory, piping the results through List.dedup to remove duplicates. Note that this example also uses some functions from other modules, including Sys.ls_dir to get a directory listing, andString.rsplit2 to split a string on the rightmost appearance of a given character:

OCaml utop (part 30)

# List.filter_map (Sys.ls_dir".") ~f:(funfname ->

matchString.rsplit2 ~on:'.'fnamewith

| None | Some ("",_) -> None

| Some (_,ext) ->

Someext)

|> List.dedup

;;

- : string list = ["ascii"; "ml"; "mli"; "topscript"]

The preceding code is also an example of an Or pattern, which allows you to have multiple subpatterns within a larger pattern. In this case, None | Some ("",_) is an Or pattern. As we’ll see later, Or patterns can be nested anywhere within larger patterns.

Partitioning with List.partition_tf

Another useful operation that’s closely related to filtering is partitioning. The function List.partition_tf takes a list and a function for computing a Boolean condition on the list elements, and returns two lists. The tf in the name is a mnemonic to remind the user that true elements go to the first list and false ones go to the second. Here’s an example:

OCaml utop (part 31)

# letis_ocaml_sources =

matchString.rsplit2s ~on:'.'with

| Some (_,("ml"|"mli")) -> true

| _ -> false

;;

val is_ocaml_source : string -> bool = <fun>

# let (ml_files,other_files) =

List.partition_tf (Sys.ls_dir".") ~f:is_ocaml_source;;

val ml_files : string list = ["example.mli"; "example.ml"]

val other_files : string list = ["main.topscript"; "lists_layout.ascii"]

Combining lists

Another very common operation on lists is concatenation. The list module actually comes with a few different ways of doing this. First, there’s List.append, for concatenating a pair of lists:

OCaml utop (part 32)

# List.append [1;2;3] [4;5;6];;

- : int list = [1; 2; 3; 4; 5; 6]

There’s also @, an operator equivalent of List.append:

OCaml utop (part 33)

# [1;2;3] @ [4;5;6];;

- : int list = [1; 2; 3; 4; 5; 6]

In addition, there is List.concat, for concatenating a list of lists:

OCaml utop (part 34)

# List.concat [[1;2];[3;4;5];[6];[]];;

- : int list = [1; 2; 3; 4; 5; 6]

Here’s an example of using List.concat along with List.map to compute a recursive listing of a directory tree:

OCaml utop (part 35)

# letrecls_recs =

ifSys.is_file_exn ~follow_symlinks:trues

then [s]

else

Sys.ls_dirs

|> List.map ~f:(funsub -> ls_rec (s ^/ sub))

|> List.concat

;;

val ls_rec : string -> string list = <fun>

Note that ^/ is an infix operator provided by Core for adding a new element to a string representing a file path. It is equivalent to Core’s Filename.concat.

The preceding combination of List.map and List.concat is common enough that there is a function List.concat_map that combines these into one, more efficient operation:

OCaml utop (part 36)

# letrecls_recs =

ifSys.is_file_exn ~follow_symlinks:trues

then [s]

else

Sys.ls_dirs

|> List.concat_map ~f:(funsub -> ls_rec (s ^/ sub))

;;

val ls_rec : string -> string list = <fun>

Tail Recursion

The only way to compute the length of an OCaml list is to walk the list from beginning to end. As a result, computing the length of a list takes time linear in the size of the list. Here’s a simple function for doing so:

OCaml utop (part 37)

# letreclength = function

| [] -> 0

| _ :: tl -> 1 + lengthtl

;;

val length : 'a list -> int = <fun>

# length [1;2;3];;

- : int = 3

This looks simple enough, but you’ll discover that this implementation runs into problems on very large lists, as we’ll show in the following code:

OCaml utop (part 38)

# letmake_listn = List.initn ~f:(funx -> x);;

val make_list : int -> int list = <fun>

# length (make_list10);;

- : int = 10

# length (make_list10_000_000);;

Stack overflow during evaluation (looping recursion?).

The preceding example creates lists using List.init, which takes an integer n and a function f and creates a list of length n, where the data for each element is created by calling f on the index of that element.

To understand where the error in the above example comes from, you need to learn a bit more about how function calls work. Typically, a function call needs some space to keep track of information associated with the call, such as the arguments passed to the function, or the location of the code that needs to start executing when the function call is complete. To allow for nested function calls, this information is typically organized in a stack, where a new stack frame is allocated for each nested function call, and then deallocated when the function call is complete.

And that’s the problem with our call to length: it tried to allocate 10 million stack frames, which exhausted the available stack space. Happily, there’s a way around this problem. Consider the following alternative implementation:

OCaml utop (part 39)

# letreclength_plus_nln =

matchlwith

| [] -> n

| _ :: tl -> length_plus_ntl (n + 1)

;;

val length_plus_n : 'a list -> int -> int = <fun>

# letlengthl = length_plus_nl0 ;;

val length : 'a list -> int = <fun>

# length [1;2;3;4];;

- : int = 4

This implementation depends on a helper function, length_plus_n, that computes the length of a given list plus a given n. In practice, n acts as an accumulator in which the answer is built up, step by step. As a result, we can do the additions along the way rather than doing them as we unwind the nested sequence of function calls, as we did in our first implementation of length.

The advantage of this approach is that the recursive call in length_plus_n is a tail call. We’ll explain more precisely what it means to be a tail call shortly, but the reason it’s important is that tail calls don’t require the allocation of a new stack frame, due to what is called the tail-call optimization. A recursive function is said to be tail recursive if all of its recursive calls are tail calls. length_plus_n is indeed tail recursive, and as a result, length can take a long list as input without blowing the stack:

OCaml utop (part 40)

# length (make_list10_000_000);;

- : int = 10000000

So when is a call a tail call? Let’s think about the situation where one function (the caller) invokes another (the callee). The invocation is considered a tail call when the caller doesn’t do anything with the value returned by the callee except to return it. The tail-call optimization makes sense because, when a caller makes a tail call, the caller’s stack frame need never be used again, and so you don’t need to keep it around. Thus, instead of allocating a new stack frame for the callee, the compiler is free to reuse the caller’s stack frame.

Tail recursion is important for more than just lists. Ordinary nontail recursive calls are reasonable when dealing with data structures like binary trees, where the depth of the tree is logarithmic in the size of your data. But when dealing with situations where the depth of the sequence of nested calls is on the order of the size of your data, tail recursion is usually the right approach.

Terser and Faster Patterns

Now that we know more about how lists and patterns work, let’s consider how we can improve on an example from Recursive list functions: the function destutter, which removes sequential duplicates from a list. Here’s the implementation that was described earlier:

OCaml utop (part 41)

# letrecdestutterlist =

matchlistwith

| [] -> []

| [hd] -> [hd]

| hd :: hd' :: tl ->

ifhd = hd'thendestutter (hd' :: tl)

elsehd :: destutter (hd' :: tl)

;;

val destutter : 'a list -> 'a list = <fun>

We’ll consider some ways of making this code more concise and more efficient.

First, let’s consider efficiency. One problem with the destutter code above is that it in some cases re-creates on the righthand side of the arrow a value that already existed on the lefthand side. Thus, the pattern [hd] -> [hd] actually allocates a new list element, when really, it should be able to just return the list being matched. We can reduce allocation here by using an as pattern, which allows us to declare a name for the thing matched by a pattern or subpattern. While we’re at it, we’ll use the function keyword to eliminate the need for an explicit match:

OCaml utop (part 42)

# letrecdestutter = function

| []asl -> l

| [_] asl -> l

| hd :: (hd' :: _ astl) ->

ifhd = hd'thendestuttertl

elsehd :: destuttertl

;;

val destutter : 'a list -> 'a list = <fun>

We can further collapse this by combining the first two cases into one, using an Or pattern:

OCaml utop (part 43)

# letrecdestutter = function

| [] | [_] asl -> l

| hd :: (hd' :: _ astl) ->

ifhd = hd'thendestuttertl

elsehd :: destuttertl

;;

val destutter : 'a list -> 'a list = <fun>

We can make the code slightly terser now by using a when clause. A when clause allows us to add an extra precondition to a pattern in the form of an arbitrary OCaml expression. In this case, we can use it to include the check on whether the first two elements are equal:

OCaml utop (part 44)

# letrecdestutter = function

| [] | [_] asl -> l

| hd :: (hd' :: _ astl) whenhd = hd' -> destuttertl

| hd :: tl -> hd :: destuttertl

;;

val destutter : 'a list -> 'a list = <fun>

POLYMORPHIC COMPARE

In the preceding destutter example, we made use of the fact that OCaml lets us test equality between values of any type, using the = operator. Thus, we can write:

OCaml utop (part 45)

# 3 = 4;;

- : bool = false

# [3;4;5] = [3;4;5];;

- : bool = true

# [Some3; None] = [None; Some3];;

- : bool = false

Indeed, if we look at the type of the equality operator, we’ll see that it is polymorphic:

OCaml utop (part 46)

# (=);;

- : 'a -> 'a -> bool = <fun>

OCaml comes with a whole family of polymorphic comparison operators, including the standard infix comparators, <, >=, etc., as well as the function compare that returns -1, 0, or 1 to flag whether the first operand is smaller than, equal to, or greater than the second, respectively.

You might wonder how you could build functions like these yourself if OCaml didn’t come with them built in. It turns out that you can’t build these functions on your own. OCaml’s polymorphic comparison functions are built into the runtime to a low level. These comparisons are polymorphic on the basis of ignoring almost everything about the types of the values that are being compared, paying attention only to the structure of the values as they’re laid out in memory.

Polymorphic compare does have some limitations. For example, it will fail at runtime if it encounters a function value:

OCaml utop (part 47)

# (funx -> x + 1) = (funx -> x + 1);;

Exception: (Invalid_argument "equal: functional value").

Similarly, it will fail on values that come from outside the OCaml heap, like values from C bindings. But it will work in a reasonable way for other kinds of values.

For simple atomic types, polymorphic compare has the semantics you would expect: for floating-point numbers and integers, polymorphic compare corresponds to the expected numerical comparison functions. For strings, it’s a lexicographic comparison.

Sometimes, however, the type-ignoring nature of polymorphic compare is a problem, particularly when you have your own notion of equality and ordering that you want to impose. We’ll discuss this issue more, as well as some of the other downsides of polymorphic compare, in Chapter 13.

Note that when clauses have some downsides. As we noted earlier, the static checks associated with pattern matches rely on the fact that patterns are restricted in what they can express. Once we add the ability to add an arbitrary condition to a pattern, something will be lost. In particular, the ability of the compiler to determine if a match is exhaustive, or if some case is redundant, is compromised.

Consider the following function, which takes a list of optional values, and returns the number of those values that are Some. Because this implementation uses when clauses, the compiler can’t tell that the code is exhaustive:

OCaml utop (part 48)

# letreccount_somelist =

matchlistwith

| [] -> 0

| x :: tlwhenOption.is_nonex -> count_sometl

| x :: tlwhenOption.is_somex -> 1 + count_sometl

;;

Characters 30-169:

Warning 8: this pattern-matching is not exhaustive.

Here is an example of a value that is not matched:

_::_

(However, some guarded clause may match this value.)

val count_some : 'a option list -> int = <fun>

Despite the warning, the function does work fine:

OCaml utop (part 49)

# count_some [Some3; None; Some4];;

- : int = 2

If we add another redundant case without a when clause, the compiler will stop complaining about exhaustiveness and won’t produce a warning about the redundancy.

OCaml utop (part 50)

# letreccount_somelist =

matchlistwith

| [] -> 0

| x :: tlwhenOption.is_nonex -> count_sometl

| x :: tlwhenOption.is_somex -> 1 + count_sometl

| x :: tl -> -1(* unreachable *)

;;

val count_some : 'a option list -> int = <fun>

Probably a better approach is to simply drop the second when clause:

OCaml utop (part 51)

# letreccount_somelist =

matchlistwith

| [] -> 0

| x :: tlwhenOption.is_nonex -> count_sometl

| _ :: tl -> 1 + count_sometl

;;

val count_some : 'a option list -> int = <fun>

This is a little less clear, however, than the direct pattern-matching solution, where the meaning of each pattern is clearer on its own:

OCaml utop (part 52)

# letreccount_somelist =

matchlistwith

| [] -> 0

| None :: tl -> count_sometl

| Some _ :: tl -> 1 + count_sometl

;;

val count_some : 'a option list -> int = <fun>

The takeaway from all of this is although when clauses can be useful, we should prefer patterns wherever they are sufficient.

As a side note, the above implementation of count_some is longer than necessary; even worse, it is not tail recursive. In real life, you would probably just use the List.count function from Core:

OCaml utop (part 53)

# letcount_somel = List.count ~f:Option.is_somel;;

val count_some : 'a option list -> int = <fun>