LogicLogic in Coq
Require Export MoreCoq.
Coq's built-in logic is very small: the only primitives are
Inductive definitions, universal quantification (∀), and
implication (→), while all the other familiar logical
connectives — conjunction, disjunction, negation, existential
quantification, even equality — can be encoded using just these.
This chapter explains the encodings and shows how the tactics
we've seen can be used to carry out standard forms of logical
reasoning involving these connectives.
Propositions
Check (3 = 3).
(* ===> Prop *)
Here is an example of an unprovable proposition:
Check (∀(n:nat), n = 2).
(* ===> Prop *)
Recall that Check asks Coq to tell us the type of the indicated
expression.
Proofs and Evidence
Lemma silly : 0 × 3 = 0.
Proof. reflexivity. Qed.
Proof. reflexivity. Qed.
Lemma silly : 0 × 3 = 0.
Proof. reflexivity. Qed.
We can see which proof term Coq constructs for a given Lemma by
using the Print directive:
Print silly.
(* ===> silly = eq_refl : 0 * 3 = 0 *)
Here, the eq_refl proof term witnesses the equality. (More on equality later!)
Just as we can implement natural number multiplication as a
function:
mult : nat → nat → nat
The proof term for an implication P → Q is a function that takes evidence for P as input and produces evidence for Q as its output.
Implications are functions
Lemma silly_implication : (1 + 1) = 2 → 0 × 3 = 0.
Proof. intros H. reflexivity. Qed.
We can see that the proof term for the above lemma is indeed a
function:
Print silly_implication.
(* ===> silly_implication = fun _ : 1 + 1 = 2 => eq_refl
: 1 + 1 = 2 -> 0 * 3 = 0 *)
Defining Propositions
- Typically, rules are defined inductively, just like any other datatype.
- Sometimes a proposition is declared to be true without substantiating evidence. Such propositions are called axioms.
Conjunction (Logical "and")
Inductive and (P Q : Prop) : Prop :=
conj : P → Q → (and P Q).
The intuition behind this definition is simple: to
construct evidence for and P Q, we must provide evidence
for P and evidence for Q. More precisely:
Since we'll be using conjunction a lot, let's introduce a more
familiar-looking infix notation for it.
- conj p q can be taken as evidence for and P Q if p
is evidence for P and q is evidence for Q; and
- this is the only way to give evidence for and P Q — that is, if someone gives us evidence for and P Q, we know it must have the form conj p q, where p is evidence for P and q is evidence for Q.
Notation "P ∧ Q" := (and P Q) : type_scope.
(The type_scope annotation tells Coq that this notation
will be appearing in propositions, not values.)
Consider the "type" of the constructor conj:
Check conj.
(* ===> forall P Q : Prop, P -> Q -> P /λ Q *)
Notice that it takes 4 inputs — namely the propositions P
and Q and evidence for P and Q — and returns as output the
evidence of P ∧ Q.
"Introducing" Conjuctions
Besides the elegance of building everything up from a tiny foundation, what's nice about defining conjunction this way is that we can prove statements involving conjunction using the tactics that we already know. For example, if the goal statement is a conjuction, we can prove it by applying the single constructor conj, which (as can be seen from the type of conj) solves the current goal and leaves the two parts of the conjunction as subgoals to be proved separately.Theorem and_example :
(0 = 0) ∧ (4 = mult 2 2).
Proof.
apply conj.
Case "left". reflexivity.
Case "right". reflexivity. Qed.
Just for convenience, we can use the tactic split as a shorthand for
apply conj.
Theorem and_example' :
(0 = 0) ∧ (4 = mult 2 2).
Proof.
split.
Case "left". reflexivity.
Case "right". reflexivity. Qed.
"Eliminating" conjunctions
Conversely, the inversion tactic can be used to take a conjunction hypothesis in the context, calculate what evidence must have been used to build it, and add variables representing this evidence to the proof context.Theorem proj1 : ∀P Q : Prop,
P ∧ Q → P.
Proof.
intros P Q H.
inversion H as [HP HQ].
apply HP. Qed.
Theorem proj2 : ∀P Q : Prop,
P ∧ Q → Q.
Proof.
(* FILL IN HERE *) Admitted.
P ∧ Q → Q.
Proof.
(* FILL IN HERE *) Admitted.
☐
Theorem and_commut : ∀P Q : Prop,
P ∧ Q → Q ∧ P.
Proof.
(* WORKED IN CLASS *)
intros P Q H.
inversion H as [HP HQ].
split.
Case "left". apply HQ.
Case "right". apply HP. Qed.
Exercise: 2 stars (and_assoc)
In the following proof, notice how the nested pattern in the inversion 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 H.
inversion H as [HP [HQ HR]].
(* FILL IN HERE *) Admitted.
☐
Definition iff (P Q : Prop) := (P → Q) ∧ (Q → P).
Notation "P ↔ Q" := (iff P Q)
(at level 95, no associativity)
: type_scope.
Theorem iff_implies : ∀P Q : Prop,
(P ↔ Q) → P → Q.
Proof.
intros P Q H.
inversion H as [HAB HBA]. apply HAB. Qed.
Theorem iff_sym : ∀P Q : Prop,
(P ↔ Q) → (Q ↔ P).
Proof.
(* WORKED IN CLASS *)
intros P Q H.
inversion H as [HAB HBA].
split.
Case "→". apply HBA.
Case "←". apply HAB. Qed.
Exercise: 1 star, 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.
Hint: If you have an iff hypothesis in the context, you can use
inversion to break it into two separate implications. (Think
about why this works.) ☐
Some of Coq's tactics treat iff statements specially, thus
avoiding the need for some low-level manipulation when reasoning
with them. In particular, rewrite can be used with iff
statements, not just equalities.
Disjunction (Logical "or")
Implementing Disjunction
Inductive or (P Q : Prop) : Prop :=
| or_introl : P → or P Q
| or_intror : Q → or P Q.
Notation "P ∨ Q" := (or P Q) : type_scope.
Consider the "type" of the constructor or_introl:
Check or_introl.
(* ===> forall P Q : Prop, P -> P λ/ Q *)
It takes 3 inputs, namely the propositions P, Q and
evidence of P, and returns, as output, the evidence of P ∨ Q.
Next, look at the type of or_intror:
Check or_intror.
(* ===> forall P Q : Prop, Q -> P λ/ Q *)
It is like or_introl but it requires evidence of Q
instead of evidence of P.
Intuitively, there are two ways of giving evidence for P ∨ Q:
- give evidence for P (and say that it is P you are giving
evidence for — this is the function of the or_introl
constructor), or
- give evidence for Q, tagged with the or_intror constructor.
Since P ∨ Q has two constructors, doing inversion on a hypothesis of type P ∨ Q yields two subgoals.
Theorem or_commut : ∀P Q : Prop,
P ∨ Q → Q ∨ P.
Proof.
intros P Q H.
inversion H as [HP | HQ].
Case "left". apply or_intror. apply HP.
Case "right". apply or_introl. apply HQ. Qed.
From here on, we'll use the shorthand tactics left and right
in place of apply or_introl and apply or_intror.
Theorem or_commut' : ∀P Q : Prop,
P ∨ Q → Q ∨ P.
Proof.
intros P Q H.
inversion H as [HP | HQ].
Case "left". right. apply HP.
Case "right". left. apply HQ. Qed.
Theorem or_distributes_over_and_1 : ∀P Q R : Prop,
P ∨ (Q ∧ R) → (P ∨ Q) ∧ (P ∨ R).
Proof.
intros P Q R. intros H. inversion H as [HP | [HQ HR]].
Case "left". split.
SCase "left". left. apply HP.
SCase "right". left. apply HP.
Case "right". split.
SCase "left". right. apply HQ.
SCase "right". right. apply HR. Qed.
Theorem or_distributes_over_and_2 : ∀P Q R : Prop,
(P ∨ Q) ∧ (P ∨ R) → P ∨ (Q ∧ R).
Proof.
(* FILL IN HERE *) Admitted.
(P ∨ Q) ∧ (P ∨ R) → P ∨ (Q ∧ 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.
☐
Relating ∧ and ∨ with andb and orb (advanced)
Theorem andb_prop : ∀b c,
andb b c = true → b = true ∧ c = true.
Proof.
(* WORKED IN CLASS *)
intros b c H.
destruct b.
Case "b = true". destruct c.
SCase "c = true". apply conj. reflexivity. reflexivity.
SCase "c = false". inversion H.
Case "b = false". inversion H. Qed.
Theorem andb_true_intro : ∀b c,
b = true ∧ c = true → andb b c = true.
Proof.
(* WORKED IN CLASS *)
intros b c H.
inversion H.
rewrite H0. rewrite H1. reflexivity. Qed.
Theorem andb_false : ∀b c,
andb b c = false → b = false ∨ c = false.
Proof.
(* FILL IN HERE *) Admitted.
Theorem orb_prop : ∀b c,
orb b c = true → b = true ∨ c = true.
Proof.
(* FILL IN HERE *) Admitted.
Theorem orb_false_elim : ∀b c,
orb b c = false → b = false ∧ c = false.
Proof.
(* FILL IN HERE *) Admitted.
andb b c = false → b = false ∨ c = false.
Proof.
(* FILL IN HERE *) Admitted.
Theorem orb_prop : ∀b c,
orb b c = true → b = true ∨ c = true.
Proof.
(* FILL IN HERE *) Admitted.
Theorem orb_false_elim : ∀b c,
orb b c = false → b = false ∧ c = false.
Proof.
(* FILL IN HERE *) Admitted.
☐
Falsehood
Inductive False : Prop := .
Intuition: False is a proposition for which there is no way
to give evidence.
Since False has no constructors, inverting an assumption
of type False always yields zero subgoals, allowing us to
immediately prove any goal.
Theorem False_implies_nonsense :
False → 2 + 2 = 5.
Proof.
intros contra.
inversion contra. Qed.
How does this work? The inversion tactic breaks contra into
each of its possible cases, and yields a subgoal for each case.
As contra is evidence for False, it has no possible cases,
hence, there are no possible subgoals and the proof is done.
Conversely, the only way to prove False is if there is already something nonsensical or contradictory in the context:
Theorem nonsense_implies_False :
2 + 2 = 5 → False.
Proof.
intros contra.
inversion contra. Qed.
Actually, since the proof of False_implies_nonsense
doesn't actually have anything to do with the specific nonsensical
thing being proved; it can easily be generalized to work for an
arbitrary P:
Theorem ex_falso_quodlibet : ∀(P:Prop),
False → P.
Proof.
(* WORKED IN CLASS *)
intros P contra.
inversion contra. Qed.
The Latin ex falso quodlibet means, literally, "from
falsehood follows whatever you please." This theorem is also
known as the principle of explosion.
Truth
Exercise: 2 stars, advanced (True)
Define True as another inductively defined proposition. (The intution is that True should be a proposition for which it is trivial to give evidence.)(* FILL IN HERE *)
☐
However, unlike False, which we'll use extensively, True is
used fairly rarely. By itself, it is trivial (and therefore
uninteresting) to prove as a goal, and it carries no useful
information as a hypothesis. But it can be useful when defining
complex Props using conditionals, or as a parameter to
higher-order Props.
Definition not (P:Prop) := P → False.
The intuition is that, if P is not true, then anything at
all (even False) follows from assuming P.
Notation "¬ x" := (not x) : type_scope.
Check not.
(* ===> Prop -> Prop *)
It takes a little practice to get used to working with
negation in Coq. Even though you can see perfectly well why
something is true, it can be a little hard at first to get things
into the right configuration so that Coq can see it! Here are
proofs of a few familiar facts about negation to get you warmed
up.
Theorem not_False :
¬ False.
Proof.
unfold not. intros H. inversion H. Qed.
Theorem contradiction_implies_anything : ∀P Q : Prop,
(P ∧ ¬P) → Q.
Proof.
(* WORKED IN CLASS *)
intros P Q H. inversion H as [HP HNA]. unfold not in HNA.
apply HNA in HP. inversion 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.
(P ∧ ¬P) → Q.
Proof.
(* WORKED IN CLASS *)
intros P Q H. inversion H as [HP HNA]. unfold not in HNA.
apply HNA in HP. inversion 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_inf)
Write an informal proof of double_neg:☐
Exercise: 2 stars (contrapositive)
Theorem contrapositive : ∀P Q : Prop,
(P → Q) → (¬Q → ¬P).
Proof.
(* FILL IN HERE *) Admitted.
(P → Q) → (¬Q → ¬P).
Proof.
(* FILL IN HERE *) Admitted.
Theorem not_both_true_and_false : ∀P : Prop,
¬ (P ∧ ¬P).
Proof.
(* FILL IN HERE *) Admitted.
¬ (P ∧ ¬P).
Proof.
(* FILL IN HERE *) Admitted.
☐
Exercise: 1 star, advanced (informal_not_PNP)
Write an informal proof (in English) of the proposition ∀ P : Prop, ~(P ∧ ¬P).(* FILL IN HERE *)
☐
Constructive logic
Note that some theorems that are true in classical logic are not provable in Coq's (constructive) logic. E.g., let's look at how this proof gets stuck...Theorem classic_double_neg : ∀P : Prop,
~~P → P.
Proof.
(* WORKED IN CLASS *)
intros P H. unfold not in H.
(* But now what? There is no way to "invent" evidence for ¬P
from evidence for P. *)
Abort.
Exercise: 5 stars, advanced, optional (classical_axioms)
For those who like a challenge, here is an exercise taken from the Coq'Art book (p. 123). The following five statements are often considered as characterizations of classical logic (as opposed to constructive logic, which is what is "built in" to Coq). We can't prove them in Coq, but we can consistently add any one of them as an unproven axiom if we wish to work in classical logic. Prove that these five propositions are equivalent.Definition peirce := ∀P Q: Prop,
((P→Q)→P)→P.
Definition classic := ∀P:Prop,
~~P → P.
Definition excluded_middle := ∀P:Prop,
P ∨ ¬P.
Definition de_morgan_not_and_not := ∀P Q:Prop,
~(~P ∧ ¬Q) → P∨Q.
Definition implies_to_or := ∀P Q:Prop,
(P→Q) → (¬P∨Q).
(* FILL IN HERE *)
☐
Exercise: 3 stars (excluded_middle_irrefutable)
This theorem implies that it is always safe to add a decidability axiom (i.e. an instance of excluded middle) for any particular Prop P. Why? Because we cannot prove the negation of such an axiom; if we could, we would have both ¬ (P ∨ ¬P) and ¬ ¬ (P ∨ ¬P), a contradiction.Theorem excluded_middle_irrefutable: ∀(P:Prop), ¬ ¬ (P ∨ ¬ P).
Proof.
(* FILL IN HERE *) Admitted.
Notation "x ≠ y" := (¬ (x = y)) : type_scope.
Since inequality involves a negation, it again requires
a little practice to be able to work with it fluently. Here
is one very useful trick. If you are trying to prove a goal
that is nonsensical (e.g., the goal state is false = true),
apply the lemma ex_falso_quodlibet to change the goal to
False. This makes it easier to use assumptions of the form
¬P that are available in the context — in particular,
assumptions of the form x≠y.
Theorem not_false_then_true : ∀b : bool,
b ≠ false → b = true.
Proof.
intros b H. destruct b.
Case "b = true". reflexivity.
Case "b = false".
unfold not in H.
apply ex_falso_quodlibet.
apply H. reflexivity. Qed.
Theorem false_beq_nat : ∀n m : nat,
n ≠ m →
beq_nat n m = false.
Proof.
(* FILL IN HERE *) Admitted.
n ≠ m →
beq_nat n m = false.
Proof.
(* FILL IN HERE *) Admitted.
Theorem beq_nat_false : ∀n m,
beq_nat n m = false → n ≠ m.
Proof.
(* FILL IN HERE *) Admitted.
beq_nat n m = false → n ≠ m.
Proof.
(* FILL IN HERE *) Admitted.
☐
(* $Date: 2013-10-12 19:54:54 -0400 (Sat, 12 Oct 2013) $ *)