Poly: Polymorphism and Higher-Order Functions
Polymorphism
Polymorphic lists
... 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.
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 type X, a binding
for X has been added to the header, 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". Observe the types of these constructors:
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 like this:
We can now go back and make polymorphic (or "generic")
versions of all the list-processing functions that we wrote
before. Here is length, for example:
Fixpoint length (X:Type) (l:list X) : nat :=
match l with
| nil => 0
| cons h t => S (length X t)
end.
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 type 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:
(We are writing nil and cons here because we haven't yet
defined the [] and :: notations. We'll do that in a
bit.)
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.
Fixpoint app (X : Type) (l1 l2 : list X)
: (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) : (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) : list X :=
match l with
| nil => nil X
| cons h t => snoc X (rev X t) h
end.
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
Fixpoint length' (X:Type) (l:list X) : 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 this...
...we can use argument synthesis to write this:
Implicit arguments
Implicit Arguments nil [[X]].
Implicit Arguments cons [[X]].
Implicit Arguments length [[X]].
Implicit Arguments app [[X]].
Implicit Arguments rev [[X]].
Implicit Arguments snoc [[X]].
Check (length list123). (* note: no _ *)
We can also conveniently declare an argument to be implicit
while defining the function itself, by surrounding the argument in
curly braces. For example:
Fixpoint length'' {X:Type} (l:list X) : nat :=
match l with
| nil => 0
| cons h t => S (length'' t)
end.
Note that in this case, we didn't even have to provide a
type argument to the recursive call to length''. We will use
this style whenever possible, although we will continue to use use
explicit Implicit Argument declarations for Inductive
constructors.
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:
Using argument synthesis and implicit arguments, 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 lists can be written just the way we'd hope:
Exercises: Polymorphic lists
Exercise: 2 stars, optional (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) : 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.
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.
forall l1 l2 : list X,
forall v : X,
snoc (l1 ++ l2) v = l1 ++ (snoc l2 v).
Proof.
(* FILL IN HERE *) Admitted.
☐
Similarly, the type definition we gave above for pairs of
numbers can be generalized to "polymorphic pairs":
Polymorphic pairs
As with lists, we make the type arguments implicit and define the
familiar concrete notation.
We can also use the Notation mechanism to define the standard
notation for pair types:
(The annotation : type_scope tells Coq that this abbreviation
should be used when parsing types.)
The first and second projection functions now look pretty
much 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.
The following function takes two lists and combines them
into a list of pairs. (In many functional programming languages,
it is called zip. We call it combine for consistency with
Coq's standard library.)
Fixpoint combine {X Y : Type} (lx : list X) (ly : list Y)
: list (X*Y) :=
match lx with
| [] => []
| x::tx => match ly with
| [] => []
| y::ty => (x,y) :: (combine tx ty)
end
end.
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".Polymorphic options
Inductive option (X:Type) : Type :=
| Some : X -> option X
| None : option X.
Implicit Arguments Some [X].
Implicit Arguments None [X].
We can now rewrite the index function so that it works
with any type of lists.
Fixpoint index
{X : Type} (n : nat)
(l : list X) : option X :=
match l with
| [] => None
| a :: l' => if beq_nat n O then Some a else index (pred n) l'
end.
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.
To force the implicit arguments to be explicit, we can use @
before the name of a function.
Check @hd_opt.
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.
☐
Like many other modern programming languages -- including,
of course, all "functional languages" -- Coq treats functions as
first-class citizens: it allows functions to be passed as
arguments to other functions, returned as results from other
functions, stored in data structures, etc.
Functions that manipulate other functions are called
"higher-order" functions. Here's a simple one:
Functions as Data
Higher-order functions
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_doit3times: doit3times minustwo 9 = 3.
Proof. reflexivity. Qed.
Example test_doit3times': doit3times negb true = false.
Proof. reflexivity. Qed.
Partial application
Check plus.
Since -> is right-associative, 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.
Digression: 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.
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.
(Thought exercise: before running these commands, can you
calculate 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.
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.
☐
Here is a useful higher-order function, which takes a list
of Xs and a predicate on X (a function from X to bool) and
"filters" the list, returning a new list containing just those
elements for which the predicate returns true.
Filter
Fixpoint filter {X:Type} (test: X->bool) (l:list X)
: (list X) :=
match l with
| [] => []
| h :: t => if test h then h :: (filter test t)
else filter test t
end.
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.
Definition length_is_1 {X : Type} (l : list X) : bool :=
beq_nat (length l) 1.
Example test_filter2:
filter length_is_1
[ [1, 2], [3], [4], [5,6,7], [], [8] ]
= [ [3], [4], [8] ].
Proof. reflexivity. Qed.
We can use filter to give a 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.
Anonymous functions
The expression fun (n:nat) => mult n n here can be read
"The function that, given a number n, returns mult n n."
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. This convenient capability is called type inference.
Here is our motivating example from before, rewritten to use
an anonymous function.
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.
Exercise: 2 stars, optional
Use filter to write a coq function partition:
partition : forall X : Type, (X -> bool) -> list X -> list X * list X
Given a set X, a test function of type X -> bool and a list
X, partition should return a pair of lists. The first member
the pair is the sublist of the original list containing the
elements that satisfy the test, and the second is the sublist
containing those that fail the test. The order of elements in the
two sublists should be the same as their order in the original
list.
Definition partition {X : Type} (test : X -> bool) (l : list X)
: list X * list X :=
(* FILL IN HERE *) admit.
Example test_partition1: partition oddb [1,2,3,4,5] = ([1,3,5], [2,4]).
(* FILL IN HERE *) Admitted.
Example test_partition2: partition (fun x => false) [5,9,0] = ([], [5,9,0]).
(* FILL IN HERE *) Admitted.
Fixpoint map {X Y:Type} (f:X->Y) (l:list X)
: (list Y) :=
match l with
| [] => []
| h :: t => (f h) :: (map f t)
end.
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:
The element types of the input and output lists need not be
the same (map takes two type arguments, X and Y). This
version of map can thus be applied to a list of numbers and a
function from numbers to booleans to yield a list of booleans:
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].
= [1, 1, 1, 5, 5, 5, 4, 4, 4].
Fixpoint flat_map {X Y:Type} (f:X -> list Y) (l:list X)
: (list Y) :=
(* FILL IN HERE *) admit.
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.
☐
Lists are not 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.
Exercise: 1 star, optional (implicit_args)
The definitions and uses of filter and map use implicit arguments in many places. Replace the curly braces around the implicit arguments with parentheses, and then fill in explicit type parameters where necessary and use Coq to check that you've done so correctly. 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. ☐Fold
Fixpoint fold {X Y:Type} (f: X->Y->Y) (l:list X) (b:Y) : Y :=
match l with
| nil => b
| h :: t => f h (fold f t b)
end.
Intuitively, the behavior of the fold operation is to
insert a given binary operator f between every pair of elements
in a given list. For example, fold plus [1,2,3,4] intuitively
means 1+2+3+4. To make this precise, we also need a "starting
element" that serves as the initial second input to f. So, for
example,
fold plus [1,2,3,4] 0
yields
1 + (2 + (3 + (4 + 0))).
Here are some more examples:
Check (fold plus).
Eval simpl in (fold plus [1,2,3,4] 0).
Example fold_example1 : fold mult [1,2,3,4] 1 = 24.
Proof. reflexivity. Qed.
Example fold_example2 : fold andb [true,true,false,true] true = false.
Proof. reflexivity. Qed.
Example fold_example3 : fold app [[1],[],[2,3],[4]] [] = [1,2,3,4].
Proof. reflexivity. Qed.
Exercise: 1 star, optional
Observe that the type of fold is parameterized by two type variables, X and Y, and the parameter f is a binary operator that takes an X and a Y and returns a Y. Can you think of a situation where it would be useful for X and Y to be different?Functions For Constructing Functions
Definition constfun {X: Type} (x: X) : nat->X :=
fun (k:nat) => x.
Definition ftrue := constfun true.
Example constfun_example1 : ftrue 0 = true.
Proof. reflexivity. Qed.
Example constfun_example2 : (constfun 5) 99 = 5.
Proof. reflexivity. Qed.
Similarly, but a bit more interestingly, here is a function
that takes a function f from numbers to some type 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) : nat->X:=
fun (k':nat) => if beq_nat k k' then x else f k'.
For example, we can apply override twice to obtain a
function from numbers to booleans that returns false on 1 and
3 and returns true on all other arguments.
Definition fmostlytrue := override (override ftrue 1 false) 3 false.
Example override_example1 : fmostlytrue 0 = true.
Proof. reflexivity. Qed.
Example override_example2 : fmostlytrue 1 = false.
Proof. reflexivity. Qed.
Example override_example3 : fmostlytrue 2 = true.
Proof. reflexivity. Qed.
Example override_example4 : fmostlytrue 3 = false.
Proof. reflexivity. Qed.
Exercise: 1 star
Before starting to work on the following proof, make sure you understand exactly what the theorem is saying and can paraphrase it in english. The proof itself is straightforward.Theorem override_example : forall (b:bool),
(override (constfun b) 3 true) 2 = b.
Proof.
(* FILL IN HERE *) Admitted.
☐
We'll use function overriding heavily in parts of the rest of the
course, and we will end up needing to know quite a bit about its
properties. To prove these properties, though, we need to know
about a few more of Coq's tactics; developing these is the main
topic of the rest of the chapter.
The precise behavior of the simpl tactic is subtle: even
expert Coq users tend to work with it by just trying it and seeing
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, these two expressions do not simplify to the same
thing.
More About Coq
The unfold tactic
The opacity of definitions shows up in other places too.
For example, there are times when a proof will get stuck because
Coq can't automatically see that two terms are equal because one
of them involves a definition.
Theorem unfold_example_bad : forall m n,
3 + n = m ->
plus3 n = m.
Proof.
intros m n H.
(* At this point, we'd like to do rewrite -> H, but it fails
because Coq doesn't realize that plus3 n is definitionally
equal to 3 + n. *)
Admitted.
The unfold tactic can be used to explicitly replace a
defined name by the right-hand side of its definition.
Theorem unfold_example : forall m n,
3 + n = m ->
plus3 n = m.
Proof.
intros m n H.
unfold plus3.
rewrite -> H.
reflexivity.
Qed.
Now we can prove a first property of override: 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.
This proof was straightforward, but note that it requires
unfold to expand the definition of override.
Exercise: 2 stars
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.
f k1 = x1 ->
beq_nat k2 k1 = false ->
(override f k2 x2) k1 = x1.
Proof.
(* FILL IN HERE *) Admitted.
☐
Recall the definition of natural numbers:
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
Then inversion H instructs Coq to "invert" this equality to
extract the information it holds about these terms:
Inversion
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:
| O : nat
| S : nat -> nat.
- 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.
c a1 a2 ... an = d b1 b2 ... bm
for some constructors c and d and arguments a1 ... a2 and
b1 ... bm.
- If c and d are the same constructor, then we know, by the
injectivity of this constructor, that a1 = b1, a2 = b2,
etc.; inversion H adds these facts to the context, and tries
to use them to rewrite the goal.
- 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 as completed and pops it off the goal stack.
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.
[n,m] = [o,o] ->
[n] = [m].
Proof.
intros n m o eq. inversion eq. reflexivity.
Qed.
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.
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.
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.
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 is 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.☐
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.
☐
Here's 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.
Practice session
Exercise: 2 stars, optional (practice)
Some nontrivial but not-too-complicated proofs to work together in class, and some for you to work as exercises. Some of the exercises may involve applying lemmas from earlier lectures or homeworks.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) :=
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'].
(* WORKED IN CLASS *)
Case "n = 0". simpl. intros m eq. destruct m as [| m'].
SCase "m = 0". reflexivity.
SCase "m = S m'". inversion eq.
Case "n = S n'". intros m eq. destruct m as [| m'].
SCase "m = 0". inversion eq.
SCase "m = S m'".
assert (n' = m') as H.
SSCase "Proof of assertion". apply IHn'. inversion eq. reflexivity.
rewrite -> H. reflexivity.
Qed.
Using tactics on hypotheses
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.
symmetry in H. apply eq in H. symmetry 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.
☐
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:
Using destruct on compound expressions
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.
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.
(override (override f k1 x2) k1 x1) k2 = (override f k1 x1) k2.
Proof.
(* FILL IN HERE *) Admitted.
☐
Hint: what property do you need of l1 and l2 for split
combine l1 l2 = (l1,l2) to be true?
State this theorem in Coq, and prove it. (Be sure to leave your
induction hypothesis general by not doing intros on more things
than necessary.)
Exercise: 2 stars
<< Theorem combine_split : 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. >> ☐Exercise: 3 stars, optional
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?
(* FILL IN HERE *)
☐
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
type 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:
The remember tactic
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).
(* stuck... *)
Admitted.
We get stuck at this point because 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.
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.
f k1 = x1 ->
(override f k1 x1) k2 = f k2.
Proof.
(* FILL IN HERE *) Admitted.
☐
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 following (silly) example uses two rewrites
in a row to get from [m,n] to [r,s] .
The apply ... with ... 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.
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 [nat] , n 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.
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
Exercise: 3 stars
Many common functions on lists can be implemented in terms of fold. For example, here is an alternate definition of length:Definition fold_length {X : Type} (l : list X) : nat :=
fold (fun _ n => S n) l 0.
Example test_fold_length1 : fold_length [4,7,0] = 3.
Proof. reflexivity. Qed.
Prove the correctness of fold_length.
Theorem fold_length_correct : forall X (l : list X),
fold_length l = length l.
(* FILL IN HERE *) Admitted.
map can also be defined in terms of fold. Define fold_map
below.
Write down a theorem in Coq stating that fold_map is correct,
and prove it.
(* FILL IN HERE *)
☐
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:
How many elements does the type baz have?
(* FILL IN HERE *)
☐
☐
Exercise: 3 stars (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:
forallb negb [false,false] = true
forallb evenb [0,2,4,5] = false
forallb (beq_nat 5) [] = true
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.
existsb (andb true) [true,true,false] = true
existsb oddb [1,0,0,0,0,3] = true
existsb evenb [] = false
>> ☐
Exercise: 2 stars, optional
Recall the definition of the index function:
Fixpoint index (X : Set) (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.
Write an informal proof of the following theorem:
match l with
| [] => None
| a :: l' => if beq_nat n O then Some a else index _ (pred n) l'
end.
forall X n l, length l = n -> index X (S n) l = None.
(* FILL IN HERE *)☐