Built with Alectryon, running Coq+SerAPI v8.10.0+0.7.0. Coq sources are in this panel; goals and messages will appear in the other. Bubbles () indicate interactive fragments: hover for details, tap to reveal contents. Use Ctrl+↑ Ctrl+↓ to navigate, Ctrl+🖱️ to focus.
This short (and optional) chapter develops some basic definitions
and a few theorems about binary relations in Coq. The key
definitions are repeated where they are actually used (in the
Smallstep chapter of Programming Language Foundations),
so readers who are already comfortable with these ideas can safely
skim or skip this chapter. However, relations are also a good
source of exercises for developing facility with Coq's basic
reasoning facilities, so it may be useful to look at this material
just after the IndProp chapter.
Set Warnings "-notation-overridden,-parsing". From LF Require Export IndProp. (* ################################################################# *)
A binary relation on a set X is a family of propositions
parameterized by two elements of X -- i.e., a proposition about
pairs of elements of X.
Definition relation (X: Type) := X -> X -> Prop.
Confusingly, the Coq standard library hijacks the generic term
"relation" for this specific instance of the idea. To maintain
consistency with the library, we will do the same. So, henceforth
the Coq identifier relation will always refer to a binary
relation between some set and itself, whereas the English word
"relation" can refer either to the specific Coq concept or the
more general concept of a relation between any number of possibly
different sets. The context of the discussion should always make
clear which is meant.
An example relation on nat is le, the less-than-or-equal-to
relation, which we usually write n1 ≤ n2.
(Why did we write it this way instead of starting with Inductive
le : relation nat...? Because we wanted to put the first nat
to the left of the :, which makes Coq generate a somewhat nicer
induction principle for reasoning about ≤.)
(* ################################################################# *)
As anyone knows who has taken an undergraduate discrete math
course, there is a lot to be said about relations in general,
including ways of classifying relations (as reflexive, transitive,
etc.), theorems that can be proved generically about certain sorts
of relations, constructions that build one relation from another,
etc. For example...
(* ----------------------------------------------------------------- *)
A relation R on a set X is a partial function if, for every
x, there is at most one y such that R x y -- i.e., R x y1
and R x y2 together imply y1 = y2.
Definition partial_function {X: Type} (R: relation X) :=
forall x y1 y2 : X, R x y1 -> R x y2 -> y1 = y2.
For example, the next_nat relation defined earlier is a partial
function.
partial_function next_natpartial_function next_natforall x y1 y2 : nat, next_nat x y1 -> next_nat x y2 -> y1 = y2x, y1, y2:natH1:next_nat x y1H2:next_nat x y2y1 = y2x, y1, y2:natH1:next_nat x y1H2:next_nat x y2n:natH:n = xH0:S x = y1S x = y2reflexivity. Qed.x, y1, y2:natH1:next_nat x y1H2:next_nat x y2n:natH:n = xH0:S x = y1n0:natH3:n0 = xH4:S x = y2S x = S x
However, the ≤ relation on numbers is not a partial
function. (Assume, for a contradiction, that ≤ is a partial
function. But then, since 0 ≤ 0 and 0 ≤ 1, it follows that
0 = 1. This is nonsense, so our assumption was
contradictory.)
~ partial_function le~ partial_function lepartial_function le -> False(forall x y1 y2 : nat, x <= y1 -> x <= y2 -> y1 = y2) -> FalseHc:forall x y1 y2 : nat, x <= y1 -> x <= y2 -> y1 = y2FalseHc:forall x y1 y2 : nat, x <= y1 -> x <= y2 -> y1 = y20 = 1Hc:forall x y1 y2 : nat, x <= y1 -> x <= y2 -> y1 = y2Nonsense:0 = 1FalseHc:forall x y1 y2 : nat, x <= y1 -> x <= y2 -> y1 = y20 = 1Hc:forall x y1 y2 : nat, x <= y1 -> x <= y2 -> y1 = y20 <= 0Hc:forall x y1 y2 : nat, x <= y1 -> x <= y2 -> y1 = y20 <= 1apply le_n.Hc:forall x y1 y2 : nat, x <= y1 -> x <= y2 -> y1 = y20 <= 0Hc:forall x y1 y2 : nat, x <= y1 -> x <= y2 -> y1 = y20 <= 1apply le_n.Hc:forall x y1 y2 : nat, x <= y1 -> x <= y2 -> y1 = y20 <= 0discriminate Nonsense. Qed.Hc:forall x y1 y2 : nat, x <= y1 -> x <= y2 -> y1 = y2Nonsense:0 = 1False
Exercise: 2 stars, standard, optional (total_relation_not_partial)
(* FILL IN HERE
[] *)
Exercise: 2 stars, standard, optional (empty_relation_partial)
(* FILL IN HERE
[] *)
(* ----------------------------------------------------------------- *)
A reflexive relation on a set X is one for which every element
of X is related to itself.
Definition reflexive {X: Type} (R: relation X) := forall a : X, R a a.reflexive lereflexive leforall a : nat, a <= aapply le_n. Qed. (* ----------------------------------------------------------------- *)n:natn <= n
A relation R is transitive if R a c holds whenever R a b
and R b c do.
Definition transitive {X: Type} (R: relation X) := forall a b c : X, (R a b) -> (R b c) -> (R a c).transitive letransitive len, m, o:natHnm:n <= mHmo:m <= on <= on, m:natHnm:n <= mn <= mn, m:natHnm:n <= mm0:natHmo:m <= m0IHHmo:n <= m0n <= S m0apply Hnm.n, m:natHnm:n <= mn <= mn, m:natHnm:n <= mm0:natHmo:m <= m0IHHmo:n <= m0n <= S m0apply IHHmo. Qed.n, m:natHnm:n <= mm0:natHmo:m <= m0IHHmo:n <= m0n <= m0transitive lttransitive lttransitive (fun n m : nat => S n <= m)forall a b c : nat, S a <= b -> S b <= c -> S a <= cn, m, o:natHnm:S n <= mHmo:S m <= oS n <= on, m, o:natHnm:S n <= S mHmo:S m <= oS n <= on, m, o:natHnm:S n <= S mHmo:S m <= oS n <= S mn, m, o:natHnm:S n <= S mHmo:S m <= oS m <= oapply Hmo. Qed.n, m, o:natHnm:S n <= S mHmo:S m <= oS m <= o
Exercise: 2 stars, standard, optional (le_trans_hard_way)
transitive lt(* Prove this by induction on evidence that [m] is less than [o]. *)transitive lttransitive (fun n m : nat => S n <= m)forall a b c : nat, S a <= b -> S b <= c -> S a <= cn, m, o:natHnm:S n <= mHmo:S m <= oS n <= o(* FILL IN HERE *) Admitted.n, m:natHnm:S n <= mS n <= S mn, m:natHnm:S n <= mm':natHm'o:S m <= m'IHHm'o:S n <= m'S n <= S m'
☐
transitive lttransitive lttransitive (fun n m : nat => S n <= m)forall a b c : nat, S a <= b -> S b <= c -> S a <= cn, m, o:natHnm:S n <= mHmo:S m <= oS n <= o(* FILL IN HERE *) Admitted.n, m:natHnm:S n <= mHmo:S m <= 0S n <= 0n, m, o':natHnm:S n <= mHmo:S m <= S o'IHo':S m <= o' -> S n <= o'S n <= S o'
☐
The transitivity of le, in turn, can be used to prove some facts
that will be useful later (e.g., for the proof of antisymmetry
below)...
forall n m : nat, S n <= m -> n <= mforall n m : nat, S n <= m -> n <= mn, m:natH:S n <= mn <= mn, m:natH:S n <= mn <= S nn, m:natH:S n <= mS n <= mn, m:natH:S n <= mn <= S napply le_n.n, m:natH:S n <= mn <= napply H. Qed.n, m:natH:S n <= mS n <= m
forall n m : nat, S n <= S m -> n <= m(* FILL IN HERE *) Admitted.forall n m : nat, S n <= S m -> n <= m
☐
Exercise: 2 stars, standard, optional (le_Sn_n_inf)
(* FILL IN HERE
[] *)
forall n : nat, ~ S n <= n(* FILL IN HERE *) Admitted.forall n : nat, ~ S n <= n
☐
Reflexivity and transitivity are the main concepts we'll need for
later chapters, but, for a bit of additional practice working with
relations in Coq, let's look at a few other common ones...
(* ----------------------------------------------------------------- *)
A relation R is symmetric if R a b implies R b a.
Definition symmetric {X: Type} (R: relation X) :=
forall a b : X, (R a b) -> (R b a).
~ symmetric le(* FILL IN HERE *) Admitted.~ symmetric le
☐
A relation R is antisymmetric if R a b and R b a together
imply a = b -- that is, if the only "cycles" in R are trivial
ones.
Definition antisymmetric {X: Type} (R: relation X) :=
forall a b : X, (R a b) -> (R b a) -> a = b.
antisymmetric le(* FILL IN HERE *) Admitted.antisymmetric le
☐
forall n m p : nat, n < m -> m <= S p -> n <= p(* FILL IN HERE *) Admitted.forall n m p : nat, n < m -> m <= S p -> n <= p
☐
(* ----------------------------------------------------------------- *)
A relation is an equivalence if it's reflexive, symmetric, and
transitive.
Definition equivalence {X:Type} (R: relation X) := (reflexive R) /\ (symmetric R) /\ (transitive R). (* ----------------------------------------------------------------- *)
A relation is a partial order when it's reflexive,
anti-symmetric, and transitive. In the Coq standard library
it's called just "order" for short.
Definition order {X:Type} (R: relation X) :=
(reflexive R) /\ (antisymmetric R) /\ (transitive R).
A preorder is almost like a partial order, but doesn't have to be
antisymmetric.
Definition preorder {X:Type} (R: relation X) := (reflexive R) /\ (transitive R).order leorder lereflexive le /\ antisymmetric le /\ transitive lereflexive leantisymmetric le /\ transitive leapply le_reflexive.reflexive leantisymmetric le /\ transitive leantisymmetric letransitive leapply le_antisymmetric.antisymmetric leapply le_trans. Qed. (* ################################################################# *)transitive le
The reflexive, transitive closure of a relation R is the
smallest relation that contains R and that is both reflexive and
transitive. Formally, it is defined like this in the Relations
module of the Coq standard library:
Inductive clos_refl_trans {A: Type} (R: relation A) : relation A :=
| rt_step x y (H : R x y) : clos_refl_trans R x y
| rt_refl x : clos_refl_trans R x x
| rt_trans x y z
(Hxy : clos_refl_trans R x y)
(Hyz : clos_refl_trans R y z) :
clos_refl_trans R x z.
For example, the reflexive and transitive closure of the
next_nat relation coincides with the le relation.
forall n m : nat, n <= m <-> clos_refl_trans next_nat n mforall n m : nat, n <= m <-> clos_refl_trans next_nat n mn, m:natn <= m <-> clos_refl_trans next_nat n mn, m:natn <= m -> clos_refl_trans next_nat n mn, m:natclos_refl_trans next_nat n m -> n <= mn, m:natn <= m -> clos_refl_trans next_nat n mn, m:natH:n <= mclos_refl_trans next_nat n mn:natclos_refl_trans next_nat n nn, m:natH:n <= mIHle:clos_refl_trans next_nat n mclos_refl_trans next_nat n (S m)apply rt_refl.n:natclos_refl_trans next_nat n nn, m:natH:n <= mIHle:clos_refl_trans next_nat n mclos_refl_trans next_nat n (S m)n, m:natH:n <= mIHle:clos_refl_trans next_nat n mclos_refl_trans next_nat n mn, m:natH:n <= mIHle:clos_refl_trans next_nat n mclos_refl_trans next_nat m (S m)n, m:natH:n <= mIHle:clos_refl_trans next_nat n mclos_refl_trans next_nat m (S m)apply nn.n, m:natH:n <= mIHle:clos_refl_trans next_nat n mnext_nat m (S m)n, m:natclos_refl_trans next_nat n m -> n <= mn, m:natH:clos_refl_trans next_nat n mn <= mx, y:natH:next_nat x yx <= yx:natx <= xx, y, z:natH:clos_refl_trans next_nat x yH0:clos_refl_trans next_nat y zIHclos_refl_trans1:x <= yIHclos_refl_trans2:y <= zx <= zx, y:natH:next_nat x yx <= yx, y:natH:next_nat x yn:natH0:n = xH1:S x = yx <= S xapply le_n.x, y:natH:next_nat x yn:natH0:n = xH1:S x = yx <= xapply le_n.x:natx <= xx, y, z:natH:clos_refl_trans next_nat x yH0:clos_refl_trans next_nat y zIHclos_refl_trans1:x <= yIHclos_refl_trans2:y <= zx <= zx, y, z:natH:clos_refl_trans next_nat x yH0:clos_refl_trans next_nat y zIHclos_refl_trans1:x <= yIHclos_refl_trans2:y <= zx <= yx, y, z:natH:clos_refl_trans next_nat x yH0:clos_refl_trans next_nat y zIHclos_refl_trans1:x <= yIHclos_refl_trans2:y <= zy <= zapply IHclos_refl_trans2. Qed.x, y, z:natH:clos_refl_trans next_nat x yH0:clos_refl_trans next_nat y zIHclos_refl_trans1:x <= yIHclos_refl_trans2:y <= zy <= z
The above definition of reflexive, transitive closure is natural:
it says, explicitly, that the reflexive and transitive closure of
R is the least relation that includes R and that is closed
under rules of reflexivity and transitivity. But it turns out
that this definition is not very convenient for doing proofs,
since the "nondeterminism" of the rt_trans rule can sometimes
lead to tricky inductions. Here is a more useful definition:
Inductive clos_refl_trans_1n {A : Type}
(R : relation A) (x : A)
: A -> Prop :=
| rt1n_refl : clos_refl_trans_1n R x x
| rt1n_trans (y z : A)
(Hxy : R x y) (Hrest : clos_refl_trans_1n R y z) :
clos_refl_trans_1n R x z.
Our new definition of reflexive, transitive closure "bundles"
the rt_step and rt_trans rules into the single rule step.
The left-hand premise of this step is a single use of R,
leading to a much simpler induction principle.
Before we go on, we should check that the two definitions do
indeed define the same relation...
First, we prove two lemmas showing that clos_refl_trans_1n mimics
the behavior of the two "missing" clos_refl_trans
constructors.
forall (X : Type) (R : relation X) (x y : X), R x y -> clos_refl_trans_1n R x yforall (X : Type) (R : relation X) (x y : X), R x y -> clos_refl_trans_1n R x yX:TypeR:relation Xx, y:XH:R x yclos_refl_trans_1n R x yX:TypeR:relation Xx, y:XH:R x yR x yX:TypeR:relation Xx, y:XH:R x yclos_refl_trans_1n R y yapply rt1n_refl. Qed.X:TypeR:relation Xx, y:XH:R x yclos_refl_trans_1n R y y
forall (X : Type) (R : relation X) (x y z : X), clos_refl_trans_1n R x y -> clos_refl_trans_1n R y z -> clos_refl_trans_1n R x z(* FILL IN HERE *) Admitted.forall (X : Type) (R : relation X) (x y z : X), clos_refl_trans_1n R x y -> clos_refl_trans_1n R y z -> clos_refl_trans_1n R x z
☐
Then we use these facts to prove that the two definitions of
reflexive, transitive closure do indeed define the same
relation.
forall (X : Type) (R : relation X) (x y : X), clos_refl_trans R x y <-> clos_refl_trans_1n R x y(* FILL IN HERE *) Admitted.forall (X : Type) (R : relation X) (x y : X), clos_refl_trans R x y <-> clos_refl_trans_1n R x y
☐
(* Wed Jan 9 12:02:46 EST 2019 *)