Poly: Polymorphism and Higher-Order Functions

(* Version of 9/13/2009 *)

Require Export Lists.

Polymorphism


Polymorphic lists


We've been working a lot with lists of numbers, but clearly programs also need to be able to manipulate lists whose elements are drawn from other types -- lists of strings, lists of booleans, lists of lists, etc. We could define a new inductive datatype for each of these...

Inductive boollist : Type :=
  | bool_nil : boollist
  | bool_cons : bool -> boollist -> boollist.

... but this would quickly become tedious, partly because we have to make up different constructor names for each datatype but mostly because we would also need to define new versions of all our list manipulating functions (length, rev, etc.) for each new datatype definition.

To avoid all this repetition, Coq supports "polymorphic" inductive type definitions. For example, here is a polymorphic list data type.

Inductive list (X:Type) : Type :=
  | nil : list X
  | cons : X -> list X -> list X.

This is exactly like the definition of natlist from the previous chapter except that the nat argument to the cons constructor has been replaced by an arbitrary set X, a binding for X has been added to the first line, and the occurrences of natlist in the types of the constructors have been replaced by list X. (We're able to re-use the constructor names nil and cons because the earlier definition of natlist was inside of a Module definition that is now out of scope

With this definition, when we use the constructors nil and cons to build lists, we need to specify what sort of lists we are building -- that is, nil and cons are now "polymorphic constructors". To see what this means, uncomment the following statements to examine the type of these constructors:

(* Check nil. *)
(* Check cons. *)

The "forall X" in these types should be read as an additional argument to the constructors that determines the expected types of the arguments that follow. When nil and cons are used, these arguments are supplied in the same way as the others. For example, the list containing 2 and 1 is written:

(* Check (cons nat 2 (cons nat 1 (nil nat))). *)

We can now go back and make polymorphic versions of all the list-processing functions that we wrote before. Here is length, for example.

Fixpoint length (X:Type) (l:list X) {struct l} : nat :=
  match l with
  | nil => 0
  | cons h t => S (length X t)
  end.

Note that the uses of nil and cons in match patterns do not require any type annotations: we already know that the list l contains elements of type X, so there's no reason to include X in the pattern. (More formally, the set X is a parameter of the whole definition of list, not of the individual constructors.)

Just as we did with nil and cons, to use length we apply it first to a type and then to its list argument:

Example test_length1 :
    length nat (cons nat 1 (cons nat 2 (nil nat))) = 2.
Proof. reflexivity. Qed.

To use our length with other kinds of lists, we simply instantiate it with an appropriate type parameter:

Example test_length2 :
    length bool (cons bool true (nil bool)) = 1.
Proof. reflexivity. Qed.

Similarly, here are polymorphic versions of app, snoc and rev.

Fixpoint app (X : Type) (l1 l2 : list X) {struct l1}
                : (list X) :=
  match l1 with
  | nil => l2
  | cons h t => cons X h (app X t l2)
  end.

Fixpoint snoc (X:Type) (l:list X) (v:X) {struct l} : (list X) :=
  match l with
  | nil => cons X v (nil X)
  | cons h t => cons X h (snoc X t v)
  end.

Fixpoint rev (X:Type) (l:list X) {struct l} : list X :=
  match l with
  | nil => nil X
  | cons h t => snoc X (rev X t) h
  end.

Here are some examples with lists of different types. Note that we are using nil and cons because we haven't yet defined the notations [] or ::.

Example test_rev1 :
    rev nat (cons nat 1 (cons nat 2 (nil nat)))
  = (cons nat 2 (cons nat 1 (nil nat))).
Proof. reflexivity. Qed.
Example test_rev2:
  rev bool (nil bool) = nil bool.
Proof. reflexivity. Qed.

Argument Synthesis


Whenever we use a polymorphic function, we need to pass it one or more sets in addition to its other arguments. For example, the recursive call in the body of the length function above must pass along the set X. But this is a bit heavy and verbose: Since the second argument to length is a list of Xs, it seems entirely obvious that the first argument can only be X -- why should we have to write it explicitly?

Fortunately, Coq permits us to avoid this kind of redundancy. In place of any type argument we can write the "implicit argument": _, which can be read "Please figure out for yourself what set belongs here." More precisely, when Coq encounters a _, it will attempt to "unify" all locally available information -- the type of the function being applied, the types of the other arguments, and the type expected by the context in which the application appears -- to determine what concrete set should replace the _.

Using implicit arguments, the length function can be written like this:

Fixpoint length' (X:Type) (l:list X) {struct l} : nat :=
  match l with
  | nil => 0
  | cons h t => S (length' _ t)
  end.

In this instance, the savings of writing _ instead of X is small. But in other cases the difference is significant. For example, suppose we want to write down a list containing the numbers 1, 2, and 3. Instead of writing

Definition l_123 :=
  cons nat 1 (cons nat 2 (cons nat 3 (nil nat))).

we can use implicit arguments to write:

Definition l_123' := cons _ 1 (cons _ 2 (cons _ 3 (nil _))).

Actually, _ can be used in place of any argument, as long as there is enough local information that Coq can determine what value is intended; but this feature is mainly used for type arguments.

Implicit arguments


To avoid writing too many _'s, we can tell Coq that we always want it to infer the type argument(s) of a given function.

Implicit Arguments nil [X].
Implicit Arguments cons [X].
Implicit Arguments length [X].
Implicit Arguments app [X].
Implicit Arguments rev [X].
Implicit Arguments snoc [X].

One small problem with declaring arguments Implicit is that, occasionally, there will not be enough local information to determine a type argument and we will need to tell Coq specially that we want to give it explicitly even though we've declared it to be Implicit. For example, if we write:

(* Definition mynil := nil. *)

Coq will give us an error, because it doesn't know what type argument to supply to nil. We can help it by providing an explicit type declaration:

Definition mynil : list nat := nil.

Now we can define convenient notation for lists, as before. Since we have made the constructor type arguments implicit, Coq will know to automatically infer the type when we use these.

Notation "x :: y" := (cons x y)
                     (at level 60, right associativity).
Notation "[ ]" := nil.
Notation "[ x , .. , y ]" := (cons x .. (cons y []) ..).
Notation "x ++ y" := (app x y)
                     (at level 60, right associativity).

Now our list can be written just the way we'd hope:

Definition l_123'' := [1, 2, 3].

Polymorphism exercises


Exercise: 2 stars (poly_exercises)

Here are a few simple exercises, just like ones in Lists.v, for practice with polymorphism. Fill in the definitions and complete the proofs below.

Fixpoint repeat (X : Type) (n : X) (count : nat) {struct count} : list X :=
  (* FILL IN HERE *) admit.

Example test_repeat1:
  repeat bool true 2 = cons true (cons true nil).
 (* FILL IN HERE *) Admitted.

Theorem nil_app : forall X:Type, forall l:list X,
  app [] l = l.
Proof.
  (* FILL IN HERE *) Admitted.

Theorem rev_snoc : forall X : Type,
                     forall v : X,
                     forall s : list X,
  rev (snoc s v) = v :: (rev s).
Proof.
  (* FILL IN HERE *) Admitted.

Exercise: 2 stars, optional

Theorem snoc_with_append : forall X : Type,
                         forall l1 l2 : list X,
                         forall v : X,
  snoc (l1 ++ l2) v = l1 ++ (snoc l2 v).
Proof.
  (* FILL IN HERE *) Admitted.

Polymorphic pairs


Similarly, the type definition we gave above for pairs of numbers can be generalized to "polymorphic pairs":

Inductive prod (X Y : Type) : Type :=
  pair : X -> Y -> prod X Y.

As with lists, we make the type arguments implicit and define the familiar concrete notation

Implicit Arguments pair [X Y].

Notation "( x , y )" := (pair x y).

We can use the same Notation mechanism to define the standard notation for pair types:

Notation "X * Y" := (prod X Y) : type_scope.

The annotation : type_scope tells Coq that this abbreviation should be used when parsing types.

The first and second projection functions now look just as they would in any functional programming language.

Definition fst (X Y : Type) (p : X * Y) : X :=
  match p with (x,y) => x end.

Definition snd (X Y : Type) (p : X * Y) : Y :=
  match p with (x,y) => y end.

Implicit Arguments snd [X Y].
Implicit Arguments fst [X Y].

The following function takes two lists and combines them into a list of pairs. In many functional programming languages, it is called "zip".

Fixpoint combine (X Y : Type) (lx : list X) (ly : list Y)
           {struct lx} : list (X*Y) :=
  match lx with
  | [] => []
  | x::tx => match ly with
             | [] => []
             | y::ty => (x,y) :: (combine _ _ tx ty)
             end
  end.

Implicit Arguments combine [X Y].

Exercise: 1 star (combine_checks)

Try answering the following questions on paper and checking your answers in coq:
  • What is the type of combine (i.e., what does Check combine print?)

  • What does

          Eval simpl in (combine [1,2] [false,false,true,true]).

    print?

Exercise: 2 stars

The function split is the inverse of combine - it takes a list of pairs and returns a pair of lists. In many functional programing languages, this function is called "unzip".

Fill in the definition of split. Make sure it passes the unit tests below.

Fixpoint split 
  (* FILL IN HERE *)

Implicit Arguments split [X Y].

Example test_split:
  split [(1,false),(2,false)] = ([1,2],[false,false]).
Proof. reflexivity.  Qed.

Polymorphic options


One last polymorphic type for now: "polymorphic options". The type declaration generalizes the one for natoption from the previous chapter

Inductive option (X:Type) : Type :=
  | Some : X -> option X
  | None : option X.

Implicit Arguments Some [X].
Implicit Arguments None [X].

Fixpoint index
             (X : Type) (n : nat)
             (l : list X) {struct l} : option X :=
  match l with
  | [] => None
  | a :: l' => if beq_nat n O then Some a else index _ (pred n) l'
  end.

Implicit Arguments index [X].

Example test_index1 : index 0 [4,5,6,7] = Some 4.
Proof. reflexivity. Qed.
Example test_index2 : index 1 [[1],[2]] = Some [2].
Proof. reflexivity. Qed.
Example test_index3 : index 2 [true] = None.
Proof. reflexivity. Qed.

Exercise: 1 star

Complete the definition of a polymorphic version of the hd_opt function from the last chapter. Be sure that it passes the unit tests below.

Definition hd_opt (X : Type) (l : list X) : option X :=
  (* FILL IN HERE *) admit.

Implicit Arguments hd_opt [X].

Example test_hd_opt1 : hd_opt [1,2] = Some 1.
 (* FILL IN HERE *) Admitted.
Example test_hd_opt2 : hd_opt [[1],[2]] = Some [1].
 (* FILL IN HERE *) Admitted.

Functions as Data


Higher-order functions


Like many other modern programming languages -- including, of course, all "functional languages" -- Coq allows functions to be passed as arguments to other functions and returned as results from other functions. Functions that operate on other functions in this way are called "higher-order" functions. Here's a simple one:

Definition doit3times (X:Type) (f:X->X) (n:X) : X :=
  f (f (f n)).

The argument f here is itself a function (from X to X); the body of doit3times applies f three times to some value n.

(* Check doit3times. *)

Example test_doit3times1: doit3times nat minustwo 9 = 3.
Proof. reflexivity. Qed.
Example test_doit3times2: doit3times bool negb true = false.
Proof. reflexivity. Qed.

Implicit Arguments doit3times [X].

Partial application


In fact, the multiple-argument functions we have already seen are also examples of higher-order functions. For instance, the type of plus is nat -> nat -> nat.

(* Check plus. *)

Since -> associates to the right, this type can equivalently be written nat -> (nat -> nat) -- i.e., it can be read as saying that "plus is a one-argument function that takes a nat and returns a one-argument function that takes another nat and returns a nat." In the examples above, we have always applied plus to both of its arguments at once, but if we like we can supply just the first. This is called "partial application."

Definition plus3 := plus 3.
(* Check plus3. *)

Example test_plus3 : plus3 4 = 7.
Proof. reflexivity. Qed.
Example test_plus3' : doit3times plus3 0 = 9.
Proof. reflexivity. Qed.
Example test_plus3'' : doit3times (plus 3) 0 = 9.
Proof. reflexivity. Qed.

Optional exercise: currying.


Exercise: 2 stars, optional (currying)

In Coq, a function f : A -> B -> C really has the type A -> (B -> C). That is, if you give f a value of type A, it will give you function f' : B -> C. If you then give f' a value of type B, it will return a value of type C. This allows for partial application, as in plus3. Processing a list of arguments with functions that return functions is called "currying", named in honor of the logician Haskell Curry.

Conversely, we can reinterpret the type A -> B -> C as (A * B) -> C. This is called "uncurrying". In an uncurried binary function, both arguments must be given at once as a pair; there is no partial application.

We can define currying as follows:

Definition prod_curry (X Y Z : Type)
  (f : X * Y -> Z) (x : X) (y : Y) : Z := f (x, y).

As an exercise, define its inverse, prod_uncurry. Then, prove the theorems below to show that the two are inverses.

Definition prod_uncurry (X Y Z : Type)
  (f : X -> Y -> Z) (p : X * Y) : Z :=
  (* FILL IN HERE *) admit.

Implicit Arguments prod_curry [X Y Z].
Implicit Arguments prod_uncurry [X Y Z].

Thought exercise: before running these commands, what are the types of prod_curry and prod_uncurry?
(* Check prod_curry. *)
(* Check prod_uncurry. *)

Theorem uncurry_curry : forall (X Y Z : Type) (f : X -> Y -> Z) x y,
  prod_curry (prod_uncurry f) x y = f x y.
Proof.
  (* FILL IN HERE *) Admitted.

Theorem curry_uncurry : forall (X Y Z : Type) (f : (X * Y) -> Z) (p : X * Y),
  prod_uncurry (prod_curry f) p = f p.
Proof.
  (* FILL IN HERE *) Admitted.

Partial application


It is also possible to construct a function "on the fly" without declaring it at the top level and giving it a name; this is analogous to the notation we've been using for writing down constant lists, etc.

Example test_anon_fun:
  doit3times (fun (n:nat) => mult n n) 2 = 256.
Proof. reflexivity. Qed.

The expression fun (n:nat) => mult n n here can be read "The function that, given a number n, returns mult n n."

It turns out we don't actually need to bother declaring the type of the argument n; Coq can see that it must be nat by looking at the context.

Example test_anon_fun':
  doit3times (fun n => mult n n) 2 = 256.
Proof. reflexivity. Qed.

Here is a slightly more complicated anonymous function

Example test_doit3times4:
  doit3times (fun n => minus (mult n 2) 1) 2 = 9.
Proof. reflexivity. Qed.

Filter


We've seen some very simple higher-order functions. Here is a more useful one, which takes a list of Xs and a predicate on X (a function from X to bool) and "filters" the list, returning just those elements for which the predicate returns true.

Fixpoint filter (X:Type) (test: X->bool) (l:list X)
                {struct l} : (list X) :=
  match l with
  | [] => []
  | h :: t => if test h then h :: (filter _ test t)
                        else filter _ test t
  end.

Implicit Arguments filter [X].

For example, if we apply filter to the predicate evenb and a list of numbers l, it returns a list containing just the even members of l.

Example test_filter1: filter evenb [1,2,3,4] = [2,4].
Proof. reflexivity. Qed.
Example test_filter2:
  filter (fun l => beq_nat (length l) 1)
         [ [1, 2], [3], [4], [5,6,7], [], [8] ]
  = [ [3], [4], [8] ].
Proof. reflexivity. Qed.

We can use filter to give a pleasantly concise version of the countoddmembers function from Lists.v.

Definition countoddmembers' (l:list nat) : nat :=
  length (filter oddb l).

Example test_countoddmembers'1: countoddmembers' [1,0,3,1,4,5] = 4.
Proof. reflexivity. Qed.
Example test_countoddmembers'2: countoddmembers' [0,2,4] = 0.
Proof. reflexivity. Qed.
Example test_countoddmembers'3: countoddmembers' nil = 0.
Proof. reflexivity. Qed.

Map


Another extremely handy higher-order function is map.

Fixpoint map (X:Type) (Y:Type) (f:X->Y) (l:list X) {struct l}
             : (list Y) :=
  match l with
  | [] => []
  | h :: t => (f h) :: (map _ _ f t)
  end.

Implicit Arguments map [X Y].

It takes a function f and a list l = [n1, n2, n3, ...] and returns the list [f n1, f n2, f n3,...] , where f has been applied to each element of l in turn. For example:

Example test_map1: map (plus 3) [2,0,2] = [5,3,5].
Proof. reflexivity. Qed.

Note that the element types of the input and output lists need not be the same (note that it takes two type arguments, X and Y). This map it can thus be applied to a list of numbers and a function from numbers to booleans to yield a list of booleans:

Example test_map2: map oddb [2,1,2,5] = [false,true,false,true].
Proof. reflexivity. Qed.

It can even be applied to a list of numbers and a function from numbers to lists of booleans to yield a list of lists of booleans:

Example test_map3:
  map (fun n => [evenb n,oddb n]) [2,1,2,5] =
  [[true,false],[false,true],[true,false],[false,true]].
Proof. reflexivity. Qed.

Exercise: 2 stars, optional

Show that map and rev commute. You may need to define an auxiliary lemma.

Theorem map_rev : forall (X Y : Type) (f : X -> Y) (l : list X),
  map f (rev l) = rev (map f l).
Proof.
  (* FILL IN HERE *) Admitted.

Exercise: 1 star

The function map maps a list X to a list Y using a function of type X -> Y. We can define a similar function, flat_map, which maps a list X to a list Y using a function f of type X -> list Y. Your definition should work by 'flattening' the results of f, like so:

    flat_map (fun n => [n,n,n]) [1,5,4]
      = [1, 1, 1, 5, 5, 5, 4, 4, 4].


Fixpoint flat_map (X:Type) (Y:Type) (f:X -> list Y) (l:list X) {struct l}
                   : (list Y) :=
  (* FILL IN HERE *) admit.

Implicit Arguments flat_map [X Y].

Example test_flat_map1:
  flat_map (fun n => [n,n,n]) [1,5,4]
  = [1, 1, 1, 5, 5, 5, 4, 4, 4].
 (* FILL IN HERE *) Admitted.

In fact, lists aren't the only inductive type that we can write a map function for. Here is the definition of map for the option type:

Definition map_option (X Y : Type) (f : X -> Y) (xo : option X)
                      : option Y :=
  match xo with
    | None => None
    | Some x => Some (f x)
  end.

Implicit Arguments map_option [X Y].

Exercise: 1 star (implicit_args)

The definitions and uses of filter and map use implicit arguments in many places. Replace every _ by an explicit set and use Coq to check that you've done so correctly. (You may also have to remove Implicit Arguments commands for Coq to accept explicit arguments.) This exercise is not to be turned in; it is probably easiest to do it on a copy of this file that you can throw away afterwards.


The unfold tactic


The precise behavior of the simpl tactic is somewhat subtle: even expert Coq users tend to just try it and see what it does in particular situations, rather than trying to predict in advance. However, one point is worth noting: simpl never expands names that have been declared as Definitions.

For example, because plus3 is a Definition, these two expressions do not simplify to the same result.

(* Eval simpl in (plus 3 5). *)
(* Eval simpl in (plus3 5). *)

The unfold tactic can be used to explicitly replace a defined name by the right-hand side of its definition. For example, we need to use it to prove this fact about plus3.

Theorem unfold_example :
  plus3 5 = 8.
Proof.
  unfold plus3.
  reflexivity.
Qed.

Functions as Data


The higher-order functions we have seen so far all take functions as arguments. Now let's look at some examples involving returning functions as the results of other functions.

To begin, here is a function that takes a value x (drawn from some set X) and returns a function from nat to X that returns x whenever it is called.

Definition constfun (X : Type) (x : X) :=
  fun (k:nat) => x.

Implicit Arguments constfun [X].

Similarly, but a bit more interestingly, here is a function that takes a function f from numbers to some set X, a number k, and a value x, and constructs a function that behaves exactly like f except that, when called with the argument k, it returns x.

Definition override (X : Type) (f : nat->X) (k:nat) (x:X) :=
  fun k' => if beq_nat k k' then x else f k'.

Implicit Arguments override [X].

We'll use function overriding heavily in parts of the rest of the course, and we will end up using quite a few of its properties. For example, we'll need to know that, if we override a function at some argument k and then look up k, we get back the overriden value.

Theorem override_eq : forall (X:Type) x k (f : nat->X),
  (override f k x) k = x.
Proof.
  intros X x k f.
  unfold override.
  rewrite <- beq_nat_refl.
  reflexivity.
Qed.

The proof of this theorem is straightforward, but note that it requires unfold to unfold the definition of override.

Exercise: 2 stars

Before starting to play with tactics, make sure you understand exactly what this theorem is saying and can paraphrase it in english.

Theorem override_example : forall (b:bool),
  (override (constfun b) 3 true) 2 = b.
Proof.
  (* FILL IN HERE *) Admitted.

Exercise: 2 stars

Prove the following theorem

Theorem override_neq : forall (X:Type) x1 x2 k1 k2 (f : nat->X),
  f k1 = x1 ->
  beq_nat k2 k1 = false ->
  (override f k2 x2) k1 = x1.
Proof.
  (* FILL IN HERE *) Admitted.

In what follows, we will see several other, more interesting, properties of override. But to prove them, we'll need to know a few more of Coq's tactics; developing these is the main topic of the next chapter.

More Coq


Symmetry


It's often quite handy to know that equality is symmetric (there's an example a bit below)...

Theorem sym_eq : forall (X : Type) (n m : X),
  n = m -> m = n.
Proof.
  intros X n m H. rewrite -> H. reflexivity.
Qed.

Inversion


Recall the definition of natural numbers:

     Inductive nat : Type :=
       | O : nat
       | S : nat -> nat.

It is clear from this definition that every number has one of two forms: either it is the constructor O or it is built by applying the constructor S to another number. But there is more here than meets the eye: implicit in the definition (and in our informal understanding of how datatype declarations work in other programming languages) are two other facts:
  • The constructor S is "injective". That is, the only way we can have S n = S m is if n = m.

  • The constructors O and S are "disjoint". That is, O is not equal to S n for any n.
Similar principles apply to all inductively defined types: all constructors are injective, and the values built from distinct constructors are never equal. For lists, the cons constructor is injective and nil is different from every non-empty list. For booleans, true and false are unequal. (Since neither true nor false take any arguments, their injectivity is not an issue.)

Coq provides a tactic, called inversion, that allows us to exploit these principles in making proofs.

The inversion tactic is used like this. Suppose H is a hypothesis in the context (or a previously proven lemma) of the form

      c a1 a2 ... an = d b1 b2 ... bm

for some constructors c and d and arguments a1 ... a2 and b1 ... bm.

Then inversion H instructs Coq to "invert" this equality to extract the information it holds about these terms:
  • If c and d are the same constructor, then we know, by the injectivity of this constructor, that a1 = b1, a2 = b2, etc., and inversion H adds these facts to the context.

  • If c and d are different constructors, then the hypothesis G is contradictory. That is, a false assumption has crept into the context, and this means that any goal whatsoever is provable! In this case, inversion H marks the current goal and completed and pops it off the goal stack.
The inversion tactic is probably easier to understand by seeing it in action than from general descriptions like the above. Below you will find example theorems which demonstrate the use of inversion and exercises to test your understanding.

Theorem eq_add_S : forall (n m : nat),
     S n = S m
  -> n = m.
Proof.
  intros n m eq. inversion eq. reflexivity.
Qed.

Theorem silly4 : forall (n m : nat),
     [n] = [m]
  -> n = m.
Proof.
  intros n o eq. inversion eq. reflexivity.
Qed.

As a convenience, the inversion tactic can also destruct equalities between complex values, binding multiple variables as it goes.
Theorem silly5 : forall (n m o : nat),
     [n,m] = [o,o]
  -> [n] = [m].
Proof.
  intros n m o eq. inversion eq. reflexivity.
Qed.

Exercise: 1 star

Example sillyex1 : forall (X : Type) (x y z : X) (l j : list X),
     x :: y :: l = z :: j
  -> y :: l = x :: j
  -> x = y.
Proof.
  (* FILL IN HERE *) Admitted.

Theorem silly6 : forall (n : nat),
     S n = O
  -> plus 2 2 = 5.
Proof.
  intros n contra. inversion contra.
Qed.

Theorem silly7 : forall (n m : nat),
     false = true
  -> [n] = [m].
Proof.
  intros n m contra. inversion contra.
Qed.

Exercise: 1 star

Example sillyex2 : forall (X : Type) (x y z : X) (l j : list X),
     x :: y :: l = []
  -> y :: l = z :: j
  -> x = z.
Proof.
  (* FILL IN HERE *) Admitted.

Here is a more realistic use of inversion to prove a property that we will find useful in many places later on...
Theorem beq_nat_eq : forall n m,
  true = beq_nat n m -> n = m.
Proof.
  intros n. induction n as [| n'].
  Case "n = 0".
    intros m. destruct m as [| m'].
    SCase "m = 0". reflexivity.
    SCase "m = S m'". simpl. intros contra. inversion contra.
  Case "n = S n'".
    intros m. destruct m as [| m'].
    SCase "m = 0". intros contra. inversion contra.
    SCase "m = S m'". simpl. intros H.
      assert (n' = m') as H1.
        apply IHn'. apply H.
      rewrite -> H1. reflexivity.
Qed.

Exercise: 2 stars (beq_nat_eq_informal)

Give an informal proof of beq_nat_eq.
Informal proof: Theorem: beq_nat equal numbers are equal. Proof: (* FILL IN HERE *)

Exercise: 1 star

Theorem override_same : forall (X:Type) x1 k1 k2 (f : nat->X),
  f k1 = x1 ->
  (override f k1 x1) k2 = f k2.
Proof.
  (* FILL IN HERE *) Admitted.

Exercise: 2 stars

We can also prove beq_nat_eq by induction on m (though we have to be a little careful about which order we introduce the variables, so that we get a general enough induction hypothesis; this is done for you below). Finish the following proof. To get maximum benefit from the exercise, try first to do it without looking back at the one above.

Theorem beq_nat_eq' : forall m n,
  beq_nat n m = true -> n = m.
Proof.
  intros m. induction m as [| m'].
  (* FILL IN HERE *) Admitted.

Another illustration of inversion. This is a slightly roundabout way of stating a fact that we have already proved above. The extra equalities force us to do a little more equational reasoning and exercise some of the tactics we've seen recently.
Theorem length_snoc' : forall (X : Type) (v : X)
                              (l : list X) (n : nat),
     length l = n
  -> length (snoc l v) = S n.
Proof.
  intros X v l. induction l as [| v' l'].
  Case "l = []". intros n eq. rewrite <- eq. reflexivity.
  Case "l = v' :: l'". intros n eq. simpl. destruct n as [| n'].
    SCase "n = 0". inversion eq.
    SCase "n = S n'".
      assert (length (snoc l' v) = S n').
        SSCase "Proof of assertion". apply IHl'.
        inversion eq. reflexivity.
      rewrite -> H. reflexivity.
Qed.

Micro-sermon: Mindless proof-hacking is a terrible temptation in Coq... Try to resist it!!

Practice session


Exercise: 2 stars (practice)

Some nontrivial but not-too-complicated proofs to work together in class, and some for you to work as exercises.

Note that some of the exercises may involve applying lemmas from earlier lectures or homeworks.

A slightly different way of making the same assertion as above.
Theorem length_snoc'' : forall (X : Type) (v : X)
                             (l : list X) (n : nat),
     S (length l) = n
  -> length (snoc l v) = n.
Proof.
  intros X v l. induction l as [| v' l'].
    Case "l = []". intros n eq. rewrite <- eq. reflexivity.
    Case "l = v' :: l'".
      intros n eq. simpl.
      (* Note the care we take here: first we introduce n
         and the equality, then we simplify.  This leaves
         the equation about length UN-simplified, which
         means our context will make a little bit more
         sense.  (The proof will work either way.) *)

      destruct n as [| n'].
      (* Now we destruct n; if it's 0, we have a
         contradiction immediately. *)

      SCase "n = 0". inversion eq.
      SCase "n = S n'".
        assert (length (snoc l' v) = n').
          SSCase "Proof of assertion".
            (* We use the IH and the inversion of eq to
               prove the equation we want about length. *)

            apply IHl'. inversion eq. reflexivity.
        rewrite -> H. reflexivity.
Qed.

Theorem beq_nat_0_l : forall n,
  true = beq_nat 0 n -> 0 = n.
Proof.
  (* FILL IN HERE *) Admitted.

Theorem beq_nat_0_r : forall n,
  true = beq_nat n 0 -> 0 = n.
Proof.
  (* FILL IN HERE *) Admitted.

Fixpoint double (n:nat) {struct n} :=
  match n with
  | O => O
  | S n' => S (S (double n'))
  end.

Theorem double_injective : forall n m,
     double n = double m
  -> n = m.
Proof.
  intros n. induction n as [| n'].
  (* FILL IN HERE *) Admitted.

Using tactics on hypotheses


By default, most tactics work on the goal formula and leave the context unchanged. But tactics often come with a variant that performs a similar operation on a statement in the context.

For example, the tactic simpl in H performs simplification in the hypothesis named H in the context.

Theorem S_inj : forall (n m : nat) (b : bool),
     beq_nat (S n) (S m) = b
  -> beq_nat n m = b.
Proof.
  intros n m b H. simpl in H. apply H.
Qed.

Similarly, the tactic apply L in H matches some conditional statement L (of the form L1 -> L2, say) against a hypothesis H in the context. However, unlike ordinary apply (which rewrites a goal matching L2 into a subgoal L1), apply L in H matches H against L1 and, if successful, replaces it with L2.

In other words, apply L in H gives us a form of "forward reasoning" -- from L1 -> L2 and a hypothesis matching L1, it gives us a hypothesis matching L2.

By contrast, apply L is "backward reasoning" -- it says that if we know L1->L2 and we are trying to prove L2, it suffices to prove L1. Here is a variant of a proof from above, using forward reasoning throughout instead of backward reasoning.

Theorem silly3' : forall (n : nat),
  (beq_nat n 5 = true -> beq_nat (S (S n)) 7 = true)
  -> true = beq_nat n 5
  -> true = beq_nat (S (S n)) 7.
Proof.
  intros n eq H.
  apply sym_eq in H. apply eq in H. apply sym_eq in H.
  apply H.
Qed.

In general, Coq tends to favor backward reasoning, but in some situations the forward style can be easier to think about.

Exercise: 2 stars

You can practice using the "in" variants in this exercise

Theorem plus_n_n_injective : forall n m,
     plus n n = plus m m
  -> n = m.
Proof.
  intros n. induction n as [| n'].
    (* Hint: use the plus_n_Sm lemma *)
    (* FILL IN HERE *) Admitted.

Using destruct on compound expressions


We have seen many examples where the destruct tactic is used to perform case analysis of the value of some variable. But sometimes we need to reason by cases on the result of some expression. We can also do this with destruct.

Here are some examples:

Definition sillyfun (n : nat) : bool :=
  if beq_nat n 3 then false
  else if beq_nat n 5 then false
  else false.

Theorem sillyfun_false : forall (n : nat),
  sillyfun n = false.
Proof.
  intros n. unfold sillyfun.
  destruct (beq_nat n 3).
    Case "beq_nat n 3 = true". reflexivity.
    Case "beq_nat n 3 = false". destruct (beq_nat n 5).
      SCase "beq_nat n 5 = true". reflexivity.
      SCase "beq_nat n 5 = false". reflexivity.
Qed.

Exercise: 1 star

Theorem override_shadow : forall (X:Type) x1 x2 k1 k2 (f : nat->X),
  (override (override f k1 x2) k1 x1) k2 = (override f k1 x1) k2.
Proof.
  (* FILL IN HERE *) Admitted.

Exercise: 2 stars

Theorem split_combine : forall X Y (l : list (X * Y)) l1 l2,
  split l = (l1, l2) ->
  combine l1 l2 = l.
Proof.
  intros X Y l. induction l as [| [x y] l'].
  (* FILL IN HERE *) Admitted.

Thought exercise: We have just proven that for all lists of pairs, combine is the inverse of split. How would you state the theorem showing that split is the inverse of combine?

Hint: what property do you need of l1 and l2 for split combine l1 l2 = (l1,l2) to be true?

The remember tactic


We have seen how the destruct tactic can be used to perform case analysis of the results of arbitrary computations. If e is an expression whose type is some inductively defined set T, then, for each constructor c of T, destruct e generates a subgoal in which all occurrences of e (in the goal and in the context) are replaced by c.

Sometimes, however, this substitution process loses information that we need in order to complete the proof. For example, suppose we define a function sillyfun1 like this:

Definition sillyfun1 (n : nat) : bool :=
  if beq_nat n 3 then true
  else if beq_nat n 5 then true
  else false.

And suppose that we want to convince Coq of the rather obvious observation that sillyfun1 n yields true only when n is odd. By analogy with the proofs we did with sillyfun above, it is natural to start the proof like this:

Theorem sillyfun1_odd_FAILED : forall (n : nat),
     sillyfun1 n = true
  -> oddb n = true.
Proof.
  intros n eq. unfold sillyfun1 in eq.
  destruct (beq_nat n 3).
Admitted.

At this point, we are stuck: the context does not contain enough information to prove the goal! The problem is that the substitution peformed by destruct is too brutal -- it threw away every occurrence of beq_nat n 3, but we need to keep at least one of these because we need to be able to reason that since, in this branch of the case analysis, beq_nat n 3 = true, it must be that n = 3, from which it follows that n is odd.

What we would really like is not to use destruct directly on beq_nat n 3 and substitute away all occurrences of this expression, but rather to use destruct on something else that is equal to beq_nat n 3 -- e.g., if we had a variable that we knew was equal to beq_nat n 3, we could destruct this variable instead.

The remember tactic allows us to introduce such a variable.

Theorem sillyfun1_odd : forall (n : nat),
     sillyfun1 n = true
  -> oddb n = true.
Proof.
  intros n eq. unfold sillyfun1 in eq.
  remember (beq_nat n 3) as e3.
  (* At this point, the context has been enriched with a new
     variable e3 and an assumption that e3 = beq_nat n 3.
     Now if we do destruct e3... *)

  destruct e3.
  (* ... the variable e3 gets substituted away (it
     disappears completely) and we are left with the same
     state as at the point where we got stuck above, except
     that the context still contains the extra equality
     assumption -- now with true substituted for e3 --
     which is exactly what we need to make progress. *)

    Case "e3 = true". apply beq_nat_eq in Heqe3.
      rewrite -> Heqe3. reflexivity.
    Case "e3 = false".
      (* When we come to the second equality test in the
         body of the function we are reasoning about, we can
         use remember again in the same way, allowing us
         to finish the proof. *)

      remember (beq_nat n 5) as e5. destruct e5.
        SCase "e5 = true".
          apply beq_nat_eq in Heqe5.
          rewrite -> Heqe5. reflexivity.
        SCase "e5 = false". inversion eq.
Qed.

Exercise: 2 stars, optional

This one is a bit challenging. Be sure your initial intros go only up through the parameter on which you want to do induction!
Theorem filter_exercise : forall (X : Type) (test : X -> bool)
                               (x : X) (l lf : list X),
     filter test l = x :: lf
  -> test x = true.
Proof.
  (* FILL IN HERE *) Admitted.

The apply ... with ... tactic


The following (silly) example uses two rewrites in a row to get from [m,n] to [r,s] .

Example trans_eq_example : forall (a b c d e f : nat),
     [a,b] = [c,d]
  -> [c,d] = [e,f]
  -> [a,b] = [e,f].
Proof.
  intros a b c d e f eq1 eq2.
  rewrite -> eq1. rewrite -> eq2. reflexivity.
Qed.

Since this is a common pattern, we might abstract it out as a lemma recording once and for all the fact that equality is transitive.

Theorem trans_eq : forall (X:Type) (n m o : X),
  n = m -> m = o -> n = o.
Proof.
  intros X n m o eq1 eq2. rewrite -> eq1. rewrite -> eq2.
  reflexivity.
Qed.

Now, we should be able to use trans_eq to prove the above example. However, to do this we need a slight refinement of the apply tactic.

Example trans_eq_example' : forall (a b c d e f : nat),
     [a,b] = [c,d]
  -> [c,d] = [e,f]
  -> [a,b] = [e,f].
Proof.
  intros a b c d e f eq1 eq2.
  (* If we simply tell Coq apply trans_eq at this point,
     it can tell (by matching the goal against the
     conclusion of the lemma) that it should instantiate X
     with natn with [a,b], and o with [e,f].
     However, the matching process doesn't determine an
     instantiation for m: we have to supply one explicitly
     by adding with (m:=[c,d]) to the invocation of
     apply. *)

  apply trans_eq with (m:=[c,d]). apply eq1. apply eq2.
Qed.

Actually, we usually don't have to include the name m in the with clause; Coq is often smart enough to figure out which instantiation we're giving. We could instead write: apply trans_eq with c,d.

Exercise: 2 stars (apply_exercises)

Example trans_eq_exercise : forall (n m o p : nat),
     m = (minustwo o)
  -> (plus n p) = m
  -> (plus n p) = (minustwo o).
Proof.
  (* FILL IN HERE *) Admitted.

Theorem beq_nat_trans : forall n m p,
  true = beq_nat n m ->
  true = beq_nat m p ->
  true = beq_nat n p.
Proof.
  (* FILL IN HERE *) Admitted.

Theorem override_permute : forall (X:Type) x1 x2 k1 k2 k3 (f : nat->X),
  false = beq_nat k2 k1 ->
  (override (override f k2 x2) k1 x1) k3 = (override (override f k1 x1) k2 x2) k3.
Proof.
  (* FILL IN HERE *) Admitted.

Additional exercises


Module MumbleBaz.

Exercise: 2 stars, optional

Consider the following two inductively defined sets.

Inductive mumble : Type :=
  | a : mumble
  | b : mumble -> nat -> mumble
  | c : mumble.
Inductive grumble (X:Type) : Type :=
  | d : mumble -> grumble X
  | e : X -> grumble X.

Which of the following are well-typed elements of grumble?
  • d (b a 5)
  • d mumble (b a 5)
  • d bool (b a 5)
  • e bool true
  • e mumble (b c 0)
  • e bool (b c 0)
  • c

Exercise: 2 stars, optional

Consider the following inductive definition:

Inductive baz : Type :=
   | x : baz -> baz
   | y : baz -> bool -> baz.

How MANY elements does the set baz have? (* FILL IN HERE *)



End MumbleBaz.

Exercise: 2 stars, optional

Consider the following Fixpoint definition:

Fixpoint fold (X:Type) (Y:Type) (f: X->Y->Y) (l:list X) (b:Y) {struct l} : Y :=
  match l with
  | nil => b
  | h :: t => f h (fold _ _ f t b)
  end.

  • What is the type of fold? (I.e., what does Check fold print?)

  • What does Check fold _ _ plus print?

  • What does

             Eval simpl in (fold _ _ plus [one,two,three,four] one)

    print?
(* FILL IN HERE *)

Exercise: 3 stars, challenge problem (forall_exists_challenge)

Challenge problem: Define two recursive Fixpoints, forallb and existsb. The first checks whether every element in a list satisfies a given predicate: [ forallb oddb [1,3,5,7,9] = true forallb negb [false,false] = true forallb evenb [0,2,4,5] = false forallb (beq_nat 5) [] = true ] existsb checks whether there exists an element in the list that satisfies a given predicate:

      existsb (beq_nat 5) [0,2,3,6] = false
 
      existsb (andb true) [true,true,false] = true
 
      existsb oddb [1,0,0,0,0,3] = true
 
      existsb evenb [] = false

Next, create a nonrecursive Definition, existsb', using forallb and negb.

Prove that existsb' and existsb have the same behavior.

(* FILL IN HERE *)
(** [] *)