Logic1: Logic in Coqpart 1
We have now seen many examples of factual claims (propositions)
and ways of presenting evidence of their truth (proofs). In
particular, we have worked extensively with equality
propositions (e1 = e2), implications (P → Q), and quantified
propositions (∀ x, P). In this chapter, we will see how
Coq can be used to carry out other familiar forms of logical
reasoning.
Before diving into details, we should talk a bit about the status of
mathematical statements in Coq. Recall that Coq is a typed
language, which means that every sensible expression has an
associated type. Logical claims are no exception: any statement
we might try to prove in Coq has a type, namely Prop, the type
of propositions. We can see this with the Check command:
Note that all syntactically well-formed propositions have type
Prop in Coq, regardless of whether they are true.
Simply being a proposition is one thing; being provable is
a different thing!
Indeed, propositions not only have types: they are
first-class entities that can be manipulated in all the same
ways as any of the other things in Coq's world.
So far, we've seen one primary place that propositions can appear:
in Theorem (and Lemma and Example) declarations.
But propositions can be used in other ways. For example, we
can give a name to a proposition using a Definition, just as we
give names to other kinds of expressions.
We can later use this name in any situation where a proposition is
expected -- for example, as the claim in a Theorem declaration.
We can also write parameterized propositions -- that is,
functions that take arguments of some type and return a
proposition.
For instance, the following function takes a number
and returns a proposition asserting that this number is equal to
three:
In Coq, functions that return propositions are said to define
properties of their arguments.
For instance, here's a (polymorphic) property defining the
familiar notion of an injective function.
Definition injective {A B} (f : A → B) : Prop :=
∀ x y : A, f x = f y → x = y.
Lemma succ_inj : injective S.
Proof.
intros n m H. injection H as H1. apply H1.
Qed.
∀ x y : A, f x = f y → x = y.
Lemma succ_inj : injective S.
Proof.
intros n m H. injection H as H1. apply H1.
Qed.
The equality operator = is a (binary) function that returns a
Prop.
The expression n = m is syntactic sugar for eq n m (defined in
Coq's standard library using the Notation mechanism). Because
eq can be used with elements of any type, it is also
polymorphic:
(Notice that we wrote @eq instead of eq: The type
argument A to eq is declared as implicit, and we need to turn
off the inference of this implicit argument to see the full type
of eq.)
Logical Connectives
Conjunction
To prove a conjunction, use the split tactic. It will generate
two subgoals, one for each part of the statement:
Proof.
split.
- (* 3 + 4 = 7 *) reflexivity.
- (* 2 * 2 = 4 *) reflexivity.
Qed.
split.
- (* 3 + 4 = 7 *) reflexivity.
- (* 2 * 2 = 4 *) reflexivity.
Qed.
For any propositions A and B, if we assume that A is true
and that B is true, we can conclude that A ∧ B is also
true.
Lemma and_intro : ∀ A B : Prop, A → B → A ∧ B.
Proof.
intros A B HA HB. split.
- apply HA.
- apply HB.
Qed.
Proof.
intros A B HA HB. split.
- apply HA.
- apply HB.
Qed.
Since applying a theorem with hypotheses to some goal has the
effect of generating as many subgoals as there are hypotheses for
that theorem, we can apply and_intro to achieve the same effect
as split.
Example and_example' : 3 + 4 = 7 ∧ 2 × 2 = 4.
Proof.
apply and_intro.
- (* 3 + 4 = 7 *) reflexivity.
- (* 2 + 2 = 4 *) reflexivity.
Qed.
Proof.
apply and_intro.
- (* 3 + 4 = 7 *) reflexivity.
- (* 2 + 2 = 4 *) reflexivity.
Qed.
Lemma and_example2 :
∀ n m : nat, n = 0 ∧ m = 0 → n + m = 0.
Proof.
(* WORKED IN CLASS *)
intros n m H.
destruct H as [Hn Hm].
rewrite Hn. rewrite Hm.
reflexivity.
Qed.
∀ n m : nat, n = 0 ∧ m = 0 → n + m = 0.
Proof.
(* WORKED IN CLASS *)
intros n m H.
destruct H as [Hn Hm].
rewrite Hn. rewrite Hm.
reflexivity.
Qed.
As usual, we can also destruct H right when we introduce it,
instead of introducing and then destructing it:
Lemma and_example2' :
∀ n m : nat, n = 0 ∧ m = 0 → n + m = 0.
Proof.
intros n m [Hn Hm].
rewrite Hn. rewrite Hm.
reflexivity.
Qed.
∀ n m : nat, n = 0 ∧ m = 0 → n + m = 0.
Proof.
intros n m [Hn Hm].
rewrite Hn. rewrite Hm.
reflexivity.
Qed.
You may wonder why we bothered packing the two hypotheses n = 0
and m = 0 into a single conjunction, since we could have also
stated the theorem with two separate premises:
Lemma and_example2'' :
∀ n m : nat, n = 0 → m = 0 → n + m = 0.
Proof.
intros n m Hn Hm.
rewrite Hn. rewrite Hm.
reflexivity.
Qed.
∀ n m : nat, n = 0 → m = 0 → n + m = 0.
Proof.
intros n m Hn Hm.
rewrite Hn. rewrite Hm.
reflexivity.
Qed.
For this specific theorem, both formulations are fine. But
it's important to understand how to work with conjunctive
hypotheses because conjunctions often arise from intermediate
steps in proofs, especially in larger developments. Here's a
simple example:
Lemma and_example3 :
∀ n m : nat, n + m = 0 → n × m = 0.
Proof.
(* WORKED IN CLASS *)
intros n m H.
apply plus_is_O in H.
destruct H as [Hn Hm].
rewrite Hn. reflexivity.
Qed.
∀ n m : nat, n + m = 0 → n × m = 0.
Proof.
(* WORKED IN CLASS *)
intros n m H.
apply plus_is_O in H.
destruct H as [Hn Hm].
rewrite Hn. reflexivity.
Qed.
Another common situation with conjunctions is that we know
A ∧ B but in some context we need just A or just B.
In such cases we can do a destruct (possibly as part of
an intros) and use an underscore pattern _ to indicate
that the unneeded conjunct should just be thrown away.
Lemma proj1 : ∀ P Q : Prop,
P ∧ Q → P.
Proof.
intros P Q HPQ.
destruct HPQ as [HP _].
apply HP. Qed.
P ∧ Q → P.
Proof.
intros P Q HPQ.
destruct HPQ as [HP _].
apply HP. Qed.
Theorem and_commut : ∀ P Q : Prop,
P ∧ Q → Q ∧ P.
Proof.
intros P Q [HP HQ].
split.
- (* left *) apply HQ.
- (* right *) apply HP. Qed.
P ∧ Q → Q ∧ P.
Proof.
intros P Q [HP HQ].
split.
- (* left *) apply HQ.
- (* right *) apply HP. Qed.
Exercise: 1 star, standard (and_assoc)
(In the following proof of associativity, notice how the nested intros pattern breaks the hypothesis H : P ∧ (Q ∧ R) down into HP : P, HQ : Q, and HR : R. Finish the proof from there.)
Theorem and_assoc : ∀ P Q R : Prop,
P ∧ (Q ∧ R) → (P ∧ Q) ∧ R.
Proof.
intros P Q R [HP [HQ HR]].
(* FILL IN HERE *) Admitted.
☐
P ∧ (Q ∧ R) → (P ∧ Q) ∧ R.
Proof.
intros P Q R [HP [HQ HR]].
(* FILL IN HERE *) Admitted.
☐
Disjunction
Lemma factor_is_O:
∀ n m : nat, n = 0 ∨ m = 0 → n × m = 0.
Proof.
(* This pattern implicitly does case analysis on
n = 0 ∨ m = 0 *)
intros n m [Hn | Hm].
- (* Here, n = 0 *)
rewrite Hn. reflexivity.
- (* Here, m = 0 *)
rewrite Hm. rewrite <- mult_n_O.
reflexivity.
Qed.
∀ n m : nat, n = 0 ∨ m = 0 → n × m = 0.
Proof.
(* This pattern implicitly does case analysis on
n = 0 ∨ m = 0 *)
intros n m [Hn | Hm].
- (* Here, n = 0 *)
rewrite Hn. reflexivity.
- (* Here, m = 0 *)
rewrite Hm. rewrite <- mult_n_O.
reflexivity.
Qed.
We can see in this example that, when we perform case analysis on a
disjunction A ∨ B, we must separately satisfy two proof
obligations, each showing that the conclusion holds under a different
assumption -- A in the first subgoal and B in the second. Note that the case analysis pattern [Hn | Hm] allows
us to name the hypotheses that are generated for the subgoals.
Conversely, to show that a disjunction holds, it suffices to show
that one of its sides holds. This can be done via two tactics,
left and right. As their names imply, the first one requires
proving the left side of the disjunction, while the second
requires proving its right side. Here is a trivial use...
... and here is a slightly more interesting example requiring both
left and right:
Lemma zero_or_succ :
∀ n : nat, n = 0 ∨ n = S (pred n).
Proof.
(* WORKED IN CLASS *)
intros [|n'].
- left. reflexivity.
- right. reflexivity.
Qed.
∀ n : nat, n = 0 ∨ n = S (pred n).
Proof.
(* WORKED IN CLASS *)
intros [|n'].
- left. reflexivity.
- right. reflexivity.
Qed.
Falsehood and Negation
So far, we have mostly been concerned with proving "positive" statements -- addition is commutative, appending lists is associative, etc. Of course, we may also be interested in negative results, demonstrating that some given proposition is not true. Such statements are expressed with the logical negation operator ¬.
Module NotPlayground.
Definition not (P:Prop) := P → False.
Notation "~ x" := (not x) : type_scope.
Check not : Prop → Prop.
End NotPlayground.
Definition not (P:Prop) := P → False.
Notation "~ x" := (not x) : type_scope.
Check not : Prop → Prop.
End NotPlayground.
Since False is a contradictory proposition, the principle of
explosion also applies to it. If we get False into the proof
context, we can use destruct on it to complete any goal:
Theorem ex_falso_quodlibet : ∀ (P:Prop),
False → P.
Proof.
(* WORKED IN CLASS *)
intros P contra.
destruct contra. Qed.
False → P.
Proof.
(* WORKED IN CLASS *)
intros P contra.
destruct contra. Qed.
The Latin ex falso quodlibet means, literally, "from falsehood
follows whatever you like"; this is another common name for the
principle of explosion.
Exercise: 2 stars, standard, optional (not_implies_our_not)
Show that Coq's definition of negation implies the intuitive one mentioned above. Hint: while getting accustomed to Coq's definition of not, you might find it helpful to unfold not near the beginning of proofs.
Theorem not_implies_our_not : ∀ (P:Prop),
¬ P → (∀ (Q:Prop), P → Q).
Proof.
(* FILL IN HERE *) Admitted.
☐
¬ P → (∀ (Q:Prop), P → Q).
Proof.
(* FILL IN HERE *) Admitted.
☐
Notation "x <> y" := (~(x = y)).
The proposition 0 ≠ 1 is exactly the same as
~(0 = 1) -- that is, not (0 = 1) -- which unfolds to
(0 = 1) → False. (We use unfold not explicitly here,
to illustrate that point, but generally it can be omitted.)
To prove an inequality, we may assume the opposite
equality...
intros contra.
... and deduce a contradiction from it. Here, the
equality O = S O contradicts the disjointness of
constructors O and S, so discriminate takes care
of it.
discriminate contra.
Qed.
Qed.
It takes a little practice to get used to working with negation in
Coq. Even though you can see perfectly well why a statement
involving negation is true, it can be a little tricky at first to
make Coq understand it! Here are proofs of a few familiar facts
to get you warmed up.
Theorem not_False :
¬ False.
Proof.
unfold not. intros H. destruct H. Qed.
Theorem contradiction_implies_anything : ∀ P Q : Prop,
(P ∧ ¬P) → Q.
Proof.
(* WORKED IN CLASS *)
intros P Q [HP HNP]. unfold not in HNP.
apply HNP in HP. destruct HP. Qed.
Theorem double_neg : ∀ P : Prop,
P → ~~P.
Proof.
(* WORKED IN CLASS *)
intros P H. unfold not. intros G. apply G. apply H. Qed.
¬ False.
Proof.
unfold not. intros H. destruct H. Qed.
Theorem contradiction_implies_anything : ∀ P Q : Prop,
(P ∧ ¬P) → Q.
Proof.
(* WORKED IN CLASS *)
intros P Q [HP HNP]. unfold not in HNP.
apply HNP in HP. destruct HP. Qed.
Theorem double_neg : ∀ P : Prop,
P → ~~P.
Proof.
(* WORKED IN CLASS *)
intros P H. unfold not. intros G. apply G. apply H. Qed.
Exercise: 2 stars, advanced (double_neg_informal)
Write an informal proof of double_neg:
(* FILL IN HERE *)
(* Do not modify the following line: *)
Definition manual_grade_for_double_neg_informal : option (nat×string) := None.
☐
(* Do not modify the following line: *)
Definition manual_grade_for_double_neg_informal : option (nat×string) := None.
☐
Exercise: 1 star, advanced (not_PNP_informal)
Write an informal proof (in English) of the proposition ∀ P : Prop, ~(P ∧ ¬P).
(* FILL IN HERE *)
(* Do not modify the following line: *)
Definition manual_grade_for_not_PNP_informal : option (nat×string) := None.
☐
(* Do not modify the following line: *)
Definition manual_grade_for_not_PNP_informal : option (nat×string) := None.
☐
Exercise: 2 stars, standard (de_morgan_not_or)
De Morgan's Laws, named for Augustus De Morgan, describe how negation interacts with conjunction and disjunction. The following law says that "the negation of a disjunction is the conjunction of the negations." There is a dual law de_morgan_not_and_not to which we will return at the end of this chapter.
Theorem de_morgan_not_or : ∀ (P Q : Prop),
¬ (P ∨ Q) → ¬P ∧ ¬Q.
Proof.
(* FILL IN HERE *) Admitted.
☐
¬ (P ∨ Q) → ¬P ∧ ¬Q.
Proof.
(* FILL IN HERE *) Admitted.
☐
Theorem not_true_is_false : ∀ b : bool,
b ≠ true → b = false.
b ≠ true → b = false.
Proof.
intros b H. destruct b eqn:HE.
- (* b = true *)
unfold not in H.
apply ex_falso_quodlibet.
apply H. reflexivity.
- (* b = false *)
reflexivity.
Qed.
intros b H. destruct b eqn:HE.
- (* b = true *)
unfold not in H.
apply ex_falso_quodlibet.
apply H. reflexivity.
- (* b = false *)
reflexivity.
Qed.
Since reasoning with ex_falso_quodlibet is quite common, Coq
provides a built-in tactic, exfalso, for applying it.
Theorem not_true_is_false' : ∀ b : bool,
b ≠ true → b = false.
Proof.
intros [] H. (* note implicit destruct b here *)
- (* b = true *)
unfold not in H.
exfalso. (* <=== *)
apply H. reflexivity.
- (* b = false *) reflexivity.
Qed.
b ≠ true → b = false.
Proof.
intros [] H. (* note implicit destruct b here *)
- (* b = true *)
unfold not in H.
exfalso. (* <=== *)
apply H. reflexivity.
- (* b = false *) reflexivity.
Qed.
Truth
Unlike False, which is used extensively, True is used
relatively rarely, since it is trivial (and therefore
uninteresting) to prove as a goal, and conversely it provides no
interesting information when used as a hypothesis.
However, True can be quite useful when defining complex Props
using conditionals or as a parameter to higher-order
Props. We'll come back to this later.
For now, let's take a look at how we can use True and False to
achieve a similar effect as the discriminate tactic, without
literally using discriminate.
Pattern-matching lets us do different things for different
constructors. If the result of applying two different
constructors were hypothetically equal, then we could use match
to convert an unprovable statement (like False) to one that is
provable (like True).
Definition disc_fn (n: nat) : Prop :=
match n with
| O ⇒ True
| S _ ⇒ False
end.
Theorem disc_example : ∀ n, ¬ (O = S n).
Proof.
intros n contra.
assert (H : disc_fn O). { simpl. apply I. }
rewrite contra in H. simpl in H. apply H.
Qed.
match n with
| O ⇒ True
| S _ ⇒ False
end.
Theorem disc_example : ∀ n, ¬ (O = S n).
Proof.
intros n contra.
assert (H : disc_fn O). { simpl. apply I. }
rewrite contra in H. simpl in H. apply H.
Qed.
To generalize this to other constructors, we simply have to
provide the appropriate generalization of disc_fn. To generalize
it to other conclusions, we can use exfalso to replace them with
False.
The built-in discriminate tactic takes care of all this for
us!
Use the same technique as above to show that nil ≠ x :: xs.
Do not use the discriminate tactic.
Exercise: 2 stars, advanced, optional (nil_is_not_cons)
Theorem nil_is_not_cons : ∀ X (x : X) (xs : list X), ¬ (nil = x :: xs).
Proof.
(* FILL IN HERE *) Admitted.
☐
Proof.
(* FILL IN HERE *) Admitted.
☐
Logical Equivalence
Module IffPlayground.
Definition iff (P Q : Prop) := (P → Q) ∧ (Q → P).
Notation "P <-> Q" := (iff P Q)
(at level 95, no associativity)
: type_scope.
End IffPlayground.
Theorem iff_sym : ∀ P Q : Prop,
(P ↔ Q) → (Q ↔ P).
Proof.
(* WORKED IN CLASS *)
intros P Q [HAB HBA].
split.
- (* -> *) apply HBA.
- (* <- *) apply HAB. Qed.
Lemma not_true_iff_false : ∀ b,
b ≠ true ↔ b = false.
Proof.
(* WORKED IN CLASS *)
intros b. split.
- (* -> *) apply not_true_is_false.
- (* <- *)
intros H. rewrite H. intros H'. discriminate H'.
Qed.
Definition iff (P Q : Prop) := (P → Q) ∧ (Q → P).
Notation "P <-> Q" := (iff P Q)
(at level 95, no associativity)
: type_scope.
End IffPlayground.
Theorem iff_sym : ∀ P Q : Prop,
(P ↔ Q) → (Q ↔ P).
Proof.
(* WORKED IN CLASS *)
intros P Q [HAB HBA].
split.
- (* -> *) apply HBA.
- (* <- *) apply HAB. Qed.
Lemma not_true_iff_false : ∀ b,
b ≠ true ↔ b = false.
Proof.
(* WORKED IN CLASS *)
intros b. split.
- (* -> *) apply not_true_is_false.
- (* <- *)
intros H. rewrite H. intros H'. discriminate H'.
Qed.
The apply tactic can also be used with ↔. We can use
apply on an ↔ in either direction, without explicitly thinking
about the fact that it is really an and underneath.
Lemma apply_iff_example1:
∀ P Q R : Prop, (P ↔ Q) → (Q → R) → (P → R).
Proof.
intros P Q R Hiff H HP. apply H. apply Hiff. apply HP.
Qed.
Lemma apply_iff_example2:
∀ P Q R : Prop, (P ↔ Q) → (P → R) → (Q → R).
Proof.
intros P Q R Hiff H HQ. apply H. apply Hiff. apply HQ.
Qed.
∀ P Q R : Prop, (P ↔ Q) → (Q → R) → (P → R).
Proof.
intros P Q R Hiff H HP. apply H. apply Hiff. apply HP.
Qed.
Lemma apply_iff_example2:
∀ P Q R : Prop, (P ↔ Q) → (P → R) → (Q → R).
Proof.
intros P Q R Hiff H HQ. apply H. apply Hiff. apply HQ.
Qed.
Exercise: 1 star, standard, optional (iff_properties)
Using the above proof that ↔ is symmetric (iff_sym) as a guide, prove that it is also reflexive and transitive.
Theorem iff_refl : ∀ P : Prop,
P ↔ P.
Proof.
(* FILL IN HERE *) Admitted.
Theorem iff_trans : ∀ P Q R : Prop,
(P ↔ Q) → (Q ↔ R) → (P ↔ R).
Proof.
(* FILL IN HERE *) Admitted.
☐
P ↔ P.
Proof.
(* FILL IN HERE *) Admitted.
Theorem iff_trans : ∀ P Q R : Prop,
(P ↔ Q) → (Q ↔ R) → (P ↔ R).
Proof.
(* FILL IN HERE *) Admitted.
☐
Theorem or_distributes_over_and : ∀ P Q R : Prop,
P ∨ (Q ∧ R) ↔ (P ∨ Q) ∧ (P ∨ R).
Proof.
(* FILL IN HERE *) Admitted.
☐
P ∨ (Q ∧ R) ↔ (P ∨ Q) ∧ (P ∨ R).
Proof.
(* FILL IN HERE *) Admitted.
☐
Setoids and Logical Equivalence
A "setoid" is a set equipped with an equivalence relation --
that is, a relation that is reflexive, symmetric, and transitive.
When two elements of a set are equivalent according to the
relation, rewrite can be used to replace one element with the
other. We've seen that already with the equality relation = in
Coq: when x = y, we can use rewrite to replace x with y,
or vice-versa.
Similarly, the logical equivalence relation ↔ is reflexive,
symmetric, and transitive, so we can use it to replace one part of
a proposition with another: if P ↔ Q, then we can use
rewrite to replace P with Q, or vice-versa.
Here is a simple example demonstrating how these tactics work with
iff. First, let's prove a couple of basic iff equivalences.
Lemma mul_eq_0 : ∀ n m, n × m = 0 ↔ n = 0 ∨ m = 0.
Theorem or_assoc :
∀ P Q R : Prop, P ∨ (Q ∨ R) ↔ (P ∨ Q) ∨ R.
Theorem or_assoc :
∀ P Q R : Prop, P ∨ (Q ∨ R) ↔ (P ∨ Q) ∨ R.
Proof.
intros P Q R. split.
- intros [H | [H | H]].
+ left. left. apply H.
+ left. right. apply H.
+ right. apply H.
- intros [[H | H] | H].
+ left. apply H.
+ right. left. apply H.
+ right. right. apply H.
Qed.
intros P Q R. split.
- intros [H | [H | H]].
+ left. left. apply H.
+ left. right. apply H.
+ right. apply H.
- intros [[H | H] | H].
+ left. apply H.
+ right. left. apply H.
+ right. right. apply H.
Qed.
We can now use these facts with rewrite and reflexivity
to give smooth proofs of statements involving equivalences. For
example, here is a ternary version of the previous mult_0
result: