Skip to content

Commit 46daa5c

Browse files
author
Alex Gryzlov
committed
first draft of Rel
1 parent f7bc505 commit 46daa5c

File tree

1 file changed

+136
-121
lines changed

1 file changed

+136
-121
lines changed

src/Rel.lidr

Lines changed: 136 additions & 121 deletions
Original file line numberDiff line numberDiff line change
@@ -93,90 +93,96 @@ for a contradiction, that \idr{<='} is a partial function. But then, since
9393
so our assumption was contradictory.)
9494
9595
> le_not_a_partial_function : Not (Partial_function Le)
96-
> le_not_a_partial_function f = ?le_not_a_partial_function_rhs
96+
> le_not_a_partial_function f = absurd $ f 0 0 1 Le_n (Le_S Le_n)
9797
9898
9999
==== Exercise: 2 stars, optional
100100
101-
Show that the total_relation defined in earlier is not a partial function.
101+
\ \todo[inline]{They mean exercises from `IndProp`}
102102
103-
(* FILL IN HERE *)
103+
Show that the idr{Total_relation} defined in earlier is not a partial function.
104+
105+
> -- FILL IN HERE
104106
105107
$\square$
106108
107109
108110
==== Exercise: 2 stars, optional
109111
110-
Show that the empty_relation that we defined earlier is a partial function.
112+
Show that the idr{Empty_relation} that we defined earlier is a partial function.
111113
112-
(* FILL IN HERE *)
114+
> --FILL IN HERE
113115
114116
$\square$
115117
116118
117119
=== Reflexive Relations
118120
119-
A reflexive relation on a set X is one for which every element of X is related
120-
to itself.
121+
A _reflexive_ relation on a set \idr{t} is one for which every element of
122+
\idr{t} is related to itself.
121123
122-
Definition reflexive {X: Type} (R: relation X) :=
123-
a : X, R a a.
124+
> Reflexive : (r : Relation t) -> Type
125+
> Reflexive {t} r = (a : t) -> r a a
124126
125-
Theorem le_reflexive :
126-
reflexive le.
127+
> le_reflexive : Reflexive Le
128+
> le_reflexive n = Le_n {n}
127129
128130
129131
=== Transitive Relations
130132
131-
A relation R is transitive if R a c holds whenever R a b and R b c do.
133+
A relation \idr{r} is _transitive_ if \idr{r a c} holds whenever \idr{r a b} and
134+
\idr{r b c} do.
135+
136+
> Transitive : (r : Relation t) -> Type
137+
> Transitive {t} r = (a, b, c : t) -> r a b -> r b c -> r a c
138+
139+
> le_trans : Transitive Le
140+
> le_trans _ _ _ lab Le_n = lab
141+
> le_trans a b (S c) lab (Le_S lbc) = Le_S $ le_trans a b c lab lbc
132142
133-
Definition transitive {X: Type} (R: relation X) :=
134-
∀a b c : X, (R a b) -> (R b c) -> (R a c).
143+
\todo[inline]{Copied here}
135144
136-
Theorem le_trans :
137-
transitive le.
145+
> Lt : (n, m : Nat) -> Type
146+
> Lt n m = Le (S n) m
138147
139-
Theorem lt_trans:
140-
transitive lt.
148+
> syntax [m] "<'" [n] = Lt m n
149+
150+
> lt_trans : Transitive Lt
151+
> lt_trans a b c lab lbc = le_trans (S a) (S b) c (Le_S lab) lbc
141152
142153
143154
==== Exercise: 2 stars, optional
144155
145-
We can also prove lt_trans more laboriously by induction, without using
146-
le_trans. Do this.
156+
We can also prove \idr{lt_trans} more laboriously by induction, without using
157+
\idr{le_trans}. Do this.
147158
148-
Theorem lt_trans' :
149-
transitive lt.
150-
Proof.
151-
(* Prove this by induction on evidence that m is less than o. *)
152-
unfold lt. unfold transitive.
153-
intros n m o Hnm Hmo.
154-
induction Hmo as [| m' Hm'o].
155-
(* FILL IN HERE *) Admitted.
159+
> lt_trans' : Transitive Lt
160+
> -- Prove this by induction on evidence that a is less than c.
161+
> lt_trans' a b c lab lbc = ?lt_trans'_rhs
156162
157163
$\square$
158164
159165
160166
==== Exercise: 2 stars, optional
161167
162-
Prove the same thing again by induction on o.
168+
Prove the same thing again by induction on \idr{c}.
163169
164-
Theorem lt_trans'' :
165-
transitive lt.
170+
> lt_trans'' : Transitive Lt
171+
> lt_trans'' a b c lab lbc = ?lt_trans'_rhs
166172
167173
$\square$
168174
169-
The transitivity of le, in turn, can be used to prove some facts that will be
170-
useful later (e.g., for the proof of antisymmetry below)...
175+
The transitivity of \idr{Le}, in turn, can be used to prove some facts that will
176+
be useful later (e.g., for the proof of antisymmetry below)...
177+
178+
> le_Sn_le : ((S n) <=' m) -> (n <=' m)
179+
> le_Sn_le {n} {m} les = le_trans n (S n) m (Le_S Le_n) les
171180
172-
Theorem le_Sn_le : ∀n m, S n ≤ m -> n ≤ m.
173181
174182
==== Exercise: 1 star, optional
175183
176-
Theorem le_S_n : ∀n m,
177-
(S n ≤ S m) -> (n ≤ m).
178-
Proof.
179-
(* FILL IN HERE *) Admitted.
184+
> le_S_n : ((S n) <=' (S m)) -> (n <=' m)
185+
> le_S_n less = ?le_S_n_rhs
180186
181187
$\square$
182188
@@ -185,22 +191,22 @@ $\square$
185191
186192
Provide an informal proof of the following theorem:
187193
188-
Theorem: For every n, ¬ (S n n)
194+
Theorem: For every \idr{n}, \idr{Not ((S n) <=' n)}
189195
190196
A formal proof of this is an optional exercise below, but try writing an
191197
informal proof without doing the formal proof first.
192198
193-
Proof: (* FILL IN HERE *)
199+
Proof:
200+
201+
> -- FILL IN HERE
194202
195203
$\square$
196204
197205
198206
==== Exercise: 1 star, optional
199207
200-
Theorem le_Sn_n : ∀n,
201-
¬ (S n ≤ n).
202-
Proof.
203-
(* FILL IN HERE *) Admitted.
208+
> le_Sn_n : Not ((S n) <=' n)
209+
> le_Sn_n = ?le_Sn_n_rhs
204210
205211
$\square$
206212
@@ -211,139 +217,148 @@ let's look at a few other common ones...
211217
212218
=== Symmetric and Antisymmetric Relations
213219
214-
A relation R is symmetric if R a b implies R b a.
220+
A relation \idr{r} is _symmetric_ if \idr{r a b} implies \idr{r b a}.
215221
216-
Definition symmetric {X: Type} (R: relation X) :=
217-
∀a b : X, (R a b) -> (R b a).
222+
> Symmetric : (r : Relation t) -> Type
223+
> Symmetric {t} r = (a, b : t) -> r a b -> r b a
218224
219225
220226
==== Exercise: 2 stars, optional
221227
222-
Theorem le_not_symmetric :
223-
¬ (symmetric le).
224-
Proof.
225-
(* FILL IN HERE *) Admitted.
228+
> le_not_symmetric : Not (Symmetric Le)
229+
> le_not_symmetric = ?le_not_symmetric_rhs
230+
226231
$\square$
227-
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.
228232
229-
Definition antisymmetric {X: Type} (R: relation X) :=
230-
∀a b : X, (R a b) -> (R b a) -> a = b.
233+
A relation \idr{r} is _antisymmetric_ if \idr{r a b{} and \idr{r b a} together
234+
imply \idr{a = b} — that is, if the only "cycles" in \idr{r} are trivial ones.
235+
236+
> Antisymmetric : (r : Relation t) -> Type
237+
> Antisymmetric {t} r = (a, b : t) -> r a b -> r b a -> a = b
231238
232239
233240
==== Exercise: 2 stars, optional
234241
235-
Theorem le_antisymmetric :
236-
antisymmetric le.
237-
Proof.
238-
(* FILL IN HERE *) Admitted.
242+
> le_antisymmetric : Antisymmetric Le
243+
> le_antisymmetric = ?le_antisymmetric_rhs
244+
239245
$\square$
240246
241247
242248
==== Exercise: 2 stars, optional
243249
244-
Theorem le_step : ∀n m p,
245-
n < m ->
246-
m ≤ S p ->
247-
n ≤ p.
248-
Proof.
249-
(* FILL IN HERE *) Admitted.
250+
> le_step : (n <' m) -> (m <=' (S p)) -> (n <=' p)
251+
> le_step ltnm lemsp = ?le_step_rhs
252+
250253
$\square$
251254
252255
253256
=== Equivalence Relations
254257
255-
A relation is an equivalence if it's reflexive, symmetric, and transitive.
258+
A relation is an _equivalence_ if it's reflexive, symmetric, and transitive.
256259
257-
Definition equivalence {X:Type} (R: relation X) :=
258-
(reflexive R) ∧ (symmetric R) ∧ (transitive R).
260+
> Equivalence : (r : Relation t) -> Type
261+
> Equivalence r = (Reflexive r, Symmetric r, Transitive r)
259262
260263
261264
=== Partial Orders and Preorders
262265
263-
A relation is a partial order when it's reflexive, anti-symmetric, and
266+
\ \todo[inline]{Edit}
267+
268+
A relation is a _partial order_ when it's reflexive, _anti_-symmetric, and
264269
transitive. In the Idris standard library it's called just "order" for short.
265270
266-
Definition order {X:Type} (R: relation X) :=
267-
(reflexive R) ∧ (antisymmetric R) ∧ (transitive R).
271+
> Order : (r : Relation t) -> Type
272+
> Order r = (Reflexive r, Antisymmetric r, Transitive r)
268273
269274
A preorder is almost like a partial order, but doesn't have to be antisymmetric.
270275
271-
Definition preorder {X:Type} (R: relation X) :=
272-
(reflexive R) ∧ (transitive R).
276+
> Preorder : (r : Relation t) -> Type
277+
> Preorder r = (Reflexive r, Transitive r)
273278
274-
Theorem le_order :
275-
order le.
279+
> le_order : Order Le
280+
> le_order = (le_reflexive, le_antisymmetric, le_trans)
276281
277282
278283
== Reflexive, Transitive Closure
279284
280-
The reflexive, transitive closure of a relation R is the smallest relation that
281-
contains R and that is both reflexive and transitive. Formally, it is defined
282-
like this in the Relations module of the Idris standard library:
285+
\ \todo[inline]{Edit}
286+
287+
The _reflexive, transitive closure_ of a relation \idr{r} is the smallest
288+
relation that contains \idr{r} and that is both reflexive and transitive.
289+
Formally, it is defined like this in the Relations module of the Idris standard
290+
library:
283291
284-
Inductive clos_refl_trans {A: Type} (R: relation A) : relation A :=
285-
| rt_step : ∀x y, R x y -> clos_refl_trans R x y
286-
| rt_refl : ∀x, clos_refl_trans R x x
287-
| rt_trans : ∀x y z,
288-
clos_refl_trans R x y ->
289-
clos_refl_trans R y z ->
290-
clos_refl_trans R x z.
292+
> data Clos_refl_trans : (r : Relation t) -> Relation t where
293+
> Rt_step : r x y -> Clos_refl_trans r x y
294+
> Rt_refl : Clos_refl_trans r x x
295+
> Rt_trans : Clos_refl_trans r x y -> Clos_refl_trans r y z ->
296+
> Clos_refl_trans r x z
291297
292-
For example, the reflexive and transitive closure of the next_nat relation
293-
coincides with the le relation.
298+
For example, the reflexive and transitive closure of the \idr{Next_nat} relation
299+
coincides with the \idr{Le} relation.
294300
295-
Theorem next_nat_closure_is_le : ∀n m,
296-
(n ≤ m) <-> ((clos_refl_trans next_nat) n m).
301+
\todo[inline]{Copied `<->` for now}
302+
303+
> iff : {p,q : Type} -> Type
304+
> iff {p} {q} = (p -> q, q -> p)
305+
>
306+
> syntax [p] "<->" [q] = iff {p} {q}
307+
308+
> next_nat_closure_is_le : (n <=' m) <-> (Clos_refl_trans Next_nat n m)
309+
> next_nat_closure_is_le = (to, fro)
310+
> where
311+
> to : Le n m -> Clos_refl_trans Next_nat n m
312+
> to Le_n = Rt_refl
313+
> to (Le_S {m} le) = Rt_trans {y=m} (to le) (Rt_step NN)
314+
> fro : Clos_refl_trans Next_nat n m -> Le n m
315+
> fro (Rt_step NN) = Le_S Le_n
316+
> fro Rt_refl = Le_n
317+
> fro (Rt_trans {x=n} {y} {z=m} ny ym) =
318+
> le_trans n y m (fro ny) (fro ym)
297319
298320
The above definition of reflexive, transitive closure is natural: it says,
299-
explicitly, that the reflexive and transitive closure of R is the least relation
300-
that includes R and that is closed under rules of reflexivity and transitivity.
301-
But it turns out that this definition is not very convenient for doing proofs,
302-
since the "nondeterminism" of the rt_trans rule can sometimes lead to tricky
303-
inductions. Here is a more useful definition:
304-
305-
Inductive clos_refl_trans_1n {A : Type}
306-
(R : relation A) (x : A)
307-
: A -> Type :=
308-
| rt1n_refl : clos_refl_trans_1n R x x
309-
| rt1n_trans (y z : A) :
310-
R x y -> clos_refl_trans_1n R y z ->
311-
clos_refl_trans_1n R x z.
312-
313-
Our new definition of reflexive, transitive closure "bundles" the rt_step and
314-
rt_trans rules into the single rule step. The left-hand premise of this step is
315-
a single use of R, leading to a much simpler induction principle.
321+
explicitly, that the reflexive and transitive closure of \idr{r} is the least
322+
relation that includes \idr{r} and that is closed under rules of reflexivity and
323+
transitivity. But it turns out that this definition is not very convenient for
324+
doing proofs, since the "nondeterminism" of the \idr{Rt_trans} rule can
325+
sometimes lead to tricky inductions. Here is a more useful definition:
326+
327+
> data Clos_refl_trans_1n : (r : Relation t) -> (x : t) -> t -> Type where
328+
> Rt1n_refl : Clos_refl_trans_1n r x x
329+
> Rt1n_trans : r x y -> Clos_refl_trans_1n r y z -> Clos_refl_trans_1n r x z
330+
331+
\todo[inline]{Edit}
332+
333+
Our new definition of reflexive, transitive closure "bundles" the \idr{Rt_step}
334+
and \idr{Rt_trans} rules into the single rule step. The left-hand premise of
335+
this step is a single use of \idr{r}, leading to a much simpler induction
336+
principle.
316337
317338
Before we go on, we should check that the two definitions do indeed define the
318339
same relation...
319340
320-
First, we prove two lemmas showing that clos_refl_trans_1n mimics the behavior
321-
of the two "missing" clos_refl_trans constructors.
341+
First, we prove two lemmas showing that \idr{Clos_refl_trans_1n} mimics the
342+
behavior of the two "missing" \idr{Clos_refl_trans} constructors.
322343
323-
Lemma rsc_R : ∀(X:Type) (R:relation X) (x y : X),
324-
R x y -> clos_refl_trans_1n R x y.
344+
> rsc_R : r x y -> Clos_refl_trans_1n r x y
345+
> rsc_R rxy = Rt1n_trans rxy Rt1n_refl
325346
326347
327348
==== Exercise: 2 stars, optional (rsc_trans)
328349
329-
Lemma rsc_trans :
330-
∀(X:Type) (R: relation X) (x y z : X),
331-
clos_refl_trans_1n R x y ->
332-
clos_refl_trans_1n R y z ->
333-
clos_refl_trans_1n R x z.
334-
Proof.
335-
(* FILL IN HERE *) Admitted.
350+
> rsc_trans : Clos_refl_trans_1n r x y -> Clos_refl_trans_1n r y z ->
351+
> Clos_refl_trans_1n r x z
352+
> rsc_trans crxy cryz = ?rsc_trans_rhs
353+
336354
$\square$
337355
338356
Then we use these facts to prove that the two definitions of reflexive, transitive closure do indeed define the same relation.
339357
340358
341359
==== Exercise: 3 stars, optional (rtc_rsc_coincide)
342360
343-
Theorem rtc_rsc_coincide :
344-
∀(X:Type) (R: relation X) (x y : X),
345-
clos_refl_trans R x y <-> clos_refl_trans_1n R x y.
346-
Proof.
347-
(* FILL IN HERE *) Admitted.
361+
> rtc_rsc_coincide : (Clos_refl_trans r x y) <-> (Clos_refl_trans_1n r x y)
362+
> rtc_rsc_coincide = ?rtc_rsc_coincide_rhs
348363
349364
$\square$

0 commit comments

Comments
 (0)