Skip to content

Commit 9a0035c

Browse files
authored
Merge pull request #33 from idris-hackers/rel
Rel
2 parents 39def30 + 777cff7 commit 9a0035c

File tree

1 file changed

+371
-0
lines changed

1 file changed

+371
-0
lines changed

src/Rel.lidr

Lines changed: 371 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,371 @@
1+
= Rel : Properties of Relations
2+
3+
> module Rel
4+
5+
\todo[inline]{Add hyperlinks}
6+
7+
This short (and optional) chapter develops some basic definitions and a few
8+
theorems about binary relations in Idris. The key definitions are repeated where
9+
they are actually used (in the `Smallstep` chapter), so readers who are already
10+
comfortable with these ideas can safely skim or skip this chapter. However,
11+
relations are also a good source of exercises for developing facility with
12+
Idris's basic reasoning facilities, so it may be useful to look at this material
13+
just after the `IndProp` chapter.
14+
15+
A binary _relation_ on a set \idr{t} is a family of propositions parameterized
16+
by two elements of \idr{t} — i.e., a proposition about pairs of elements of
17+
\idr{t}.
18+
19+
> Relation : Type -> Type
20+
> Relation t = t -> t -> Type
21+
22+
\todo[inline]{Edit, there's n-relation \idr{Data.Rel} in \idr{contrib}, but no
23+
\idr{Relation}}
24+
25+
Confusingly, the Idris standard library hijacks the generic term "relation" for
26+
this specific instance of the idea. To maintain consistency with the library, we
27+
will do the same. So, henceforth the Idris identifier `relation` will always
28+
refer to a binary relation between some set and itself, whereas the English word
29+
"relation" can refer either to the specific Idris concept or the more general
30+
concept of a relation between any number of possibly different sets. The context
31+
of the discussion should always make clear which is meant.
32+
33+
\todo[inline]{There's a similar concept called \idr{LTE} in \idr{Prelude.Nat},
34+
but it's defined by induction from zero}
35+
36+
An example relation on \idr{Nat} is \idr{Le}, the less-than-or-equal-to
37+
relation, which we usually write \idr{n1 <= n2}.
38+
39+
\todo[inline]{Copied from `IndProp`}
40+
41+
> data Le : (n : Nat) -> Nat -> Type where
42+
> Le_n : Le n n
43+
> Le_S : Le n m -> Le n (S m)
44+
>
45+
> syntax [m] "<='" [n] = Le m n
46+
47+
```idris
48+
λΠ> the (Relation Nat) Le
49+
Le : Nat -> Nat -> Type
50+
```
51+
52+
\todo[inline]{Edit to show it (probably) doesn't matter in Idris}
53+
54+
(Why did we write it this way instead of starting with \idr{data Le : Relation
55+
Nat ...}? Because we wanted to put the first \idr{Nat} to the left of the
56+
\idr{:}, which makes Idris generate a somewhat nicer induction principle for
57+
reasoning about \idr{<='}.)
58+
59+
60+
== Basic Properties
61+
62+
As anyone knows who has taken an undergraduate discrete math course, there is a
63+
lot to be said about relations in general, including ways of classifying
64+
relations (as reflexive, transitive, etc.), theorems that can be proved
65+
generically about certain sorts of relations, constructions that build one
66+
relation from another, etc. For example...
67+
68+
69+
=== Partial Functions
70+
71+
A relation \idr{r} on a set \idr{t} is a _partial function_ if, for every
72+
\idr{x}, there is at most one \idr{y} such that \idr{r x y} — i.e., \idr{r x y1}
73+
and \idr{r x y2} together imply \idr{y1 = y2}.
74+
75+
> Partial_function : (r : Relation t) -> Type
76+
> Partial_function {t} r = (x, y1, y2 : t) -> r x y1 -> r x y2 -> y1 = y2
77+
78+
\todo[inline]{"Earlier" = in \idr{IndProp}, add hyperlink?}
79+
80+
For example, the \idr{Next_nat} relation defined earlier is a partial function.
81+
82+
> data Next_nat : (n : Nat) -> Nat -> Type where
83+
> NN : Next_nat n (S n)
84+
85+
```idris
86+
λΠ> the (Relation Nat) Next_nat
87+
Next_nat : Nat -> Nat -> Type
88+
```
89+
90+
> next_nat_partial_function : Partial_function Next_nat
91+
> next_nat_partial_function x (S x) (S x) NN NN = Refl
92+
93+
However, the \idr{<='} relation on numbers is not a partial function. (Assume,
94+
for a contradiction, that \idr{<='} is a partial function. But then, since
95+
\idr{0 <=' 0} and \idr{0 <=' 1}, it follows that \idr{0 = 1}. This is nonsense,
96+
so our assumption was contradictory.)
97+
98+
> le_not_a_partial_function : Not (Partial_function Le)
99+
> le_not_a_partial_function f = absurd $ f 0 0 1 Le_n (Le_S Le_n)
100+
101+
102+
==== Exercise: 2 stars, optional
103+
104+
\ \todo[inline]{Again, "earlier" = \idr{IndProp}}
105+
106+
Show that the \idr{Total_relation} defined in earlier is not a partial function.
107+
108+
> -- FILL IN HERE
109+
110+
$\square$
111+
112+
113+
==== Exercise: 2 stars, optional
114+
115+
Show that the \idr{Empty_relation} that we defined earlier is a partial
116+
function.
117+
118+
> --FILL IN HERE
119+
120+
$\square$
121+
122+
123+
=== Reflexive Relations
124+
125+
A _reflexive_ relation on a set \idr{t} is one for which every element of
126+
\idr{t} is related to itself.
127+
128+
> Reflexive : (r : Relation t) -> Type
129+
> Reflexive {t} r = (a : t) -> r a a
130+
131+
> le_reflexive : Reflexive Le
132+
> le_reflexive n = Le_n {n}
133+
134+
135+
=== Transitive Relations
136+
137+
A relation \idr{r} is _transitive_ if \idr{r a c} holds whenever \idr{r a b} and
138+
\idr{r b c} do.
139+
140+
> Transitive : (r : Relation t) -> Type
141+
> Transitive {t} r = (a, b, c : t) -> r a b -> r b c -> r a c
142+
143+
> le_trans : Transitive Le
144+
> le_trans _ _ _ lab Le_n = lab
145+
> le_trans a b (S c) lab (Le_S lbc) = Le_S $ le_trans a b c lab lbc
146+
147+
\todo[inline]{Copied here}
148+
149+
> Lt : (n, m : Nat) -> Type
150+
> Lt n m = Le (S n) m
151+
152+
> syntax [m] "<'" [n] = Lt m n
153+
154+
> lt_trans : Transitive Lt
155+
> lt_trans a b c lab lbc = le_trans (S a) (S b) c (Le_S lab) lbc
156+
157+
158+
==== Exercise: 2 stars, optional
159+
160+
We can also prove \idr{lt_trans} more laboriously by induction, without using
161+
\idr{le_trans}. Do this.
162+
163+
> lt_trans' : Transitive Lt
164+
> -- Prove this by induction on evidence that a is less than c.
165+
> lt_trans' a b c lab lbc = ?lt_trans__rhs
166+
167+
$\square$
168+
169+
170+
==== Exercise: 2 stars, optional
171+
172+
\ \todo[inline]{Not sure how is this different from \idr{lt_trans'}?}
173+
174+
Prove the same thing again by induction on \idr{c}.
175+
176+
> lt_trans'' : Transitive Lt
177+
> lt_trans'' a b c lab lbc = ?lt_trans___rhs
178+
179+
$\square$
180+
181+
The transitivity of \idr{Le}, in turn, can be used to prove some facts that will
182+
be useful later (e.g., for the proof of antisymmetry below)...
183+
184+
> le_Sn_le : ((S n) <=' m) -> (n <=' m)
185+
> le_Sn_le {n} {m} = le_trans n (S n) m (Le_S Le_n)
186+
187+
188+
==== Exercise: 1 star, optional
189+
190+
> le_S_n : ((S n) <=' (S m)) -> (n <=' m)
191+
> le_S_n less = ?le_S_n_rhs
192+
193+
$\square$
194+
195+
196+
==== Exercise: 2 stars, optional (le_Sn_n_inf)
197+
198+
Provide an informal proof of the following theorem:
199+
200+
Theorem: For every \idr{n}, \idr{Not ((S n) <=' n)}
201+
202+
A formal proof of this is an optional exercise below, but try writing an
203+
informal proof without doing the formal proof first.
204+
205+
Proof:
206+
207+
> -- FILL IN HERE
208+
209+
$\square$
210+
211+
212+
==== Exercise: 1 star, optional
213+
214+
> le_Sn_n : Not ((S n) <=' n)
215+
> le_Sn_n = ?le_Sn_n_rhs
216+
217+
$\square$
218+
219+
Reflexivity and transitivity are the main concepts we'll need for later
220+
chapters, but, for a bit of additional practice working with relations in Idris,
221+
let's look at a few other common ones...
222+
223+
224+
=== Symmetric and Antisymmetric Relations
225+
226+
A relation \idr{r} is _symmetric_ if \idr{r a b} implies \idr{r b a}.
227+
228+
> Symmetric : (r : Relation t) -> Type
229+
> Symmetric {t} r = (a, b : t) -> r a b -> r b a
230+
231+
232+
==== Exercise: 2 stars, optional
233+
234+
> le_not_symmetric : Not (Symmetric Le)
235+
> le_not_symmetric = ?le_not_symmetric_rhs
236+
237+
$\square$
238+
239+
A relation \idr{r} is _antisymmetric_ if \idr{r a b} and \idr{r b a} together
240+
imply \idr{a = b} — that is, if the only "cycles" in \idr{r} are trivial ones.
241+
242+
> Antisymmetric : (r : Relation t) -> Type
243+
> Antisymmetric {t} r = (a, b : t) -> r a b -> r b a -> a = b
244+
245+
246+
==== Exercise: 2 stars, optional
247+
248+
> le_antisymmetric : Antisymmetric Le
249+
> le_antisymmetric = ?le_antisymmetric_rhs
250+
251+
$\square$
252+
253+
254+
==== Exercise: 2 stars, optional
255+
256+
> le_step : (n <' m) -> (m <=' (S p)) -> (n <=' p)
257+
> le_step ltnm lemsp = ?le_step_rhs
258+
259+
$\square$
260+
261+
262+
=== Equivalence Relations
263+
264+
A relation is an _equivalence_ if it's reflexive, symmetric, and transitive.
265+
266+
> Equivalence : (r : Relation t) -> Type
267+
> Equivalence r = (Reflexive r, Symmetric r, Transitive r)
268+
269+
270+
=== Partial Orders and Preorders
271+
272+
\ \todo[inline]{Edit}
273+
274+
A relation is a _partial order_ when it's reflexive, _anti_-symmetric, and
275+
transitive. In the Idris standard library it's called just "order" for short.
276+
277+
> Order : (r : Relation t) -> Type
278+
> Order r = (Reflexive r, Antisymmetric r, Transitive r)
279+
280+
A preorder is almost like a partial order, but doesn't have to be antisymmetric.
281+
282+
> Preorder : (r : Relation t) -> Type
283+
> Preorder r = (Reflexive r, Transitive r)
284+
285+
> le_order : Order Le
286+
> le_order = (le_reflexive, le_antisymmetric, le_trans)
287+
288+
289+
== Reflexive, Transitive Closure
290+
291+
\ \todo[inline]{Edit}
292+
293+
The _reflexive, transitive closure_ of a relation \idr{r} is the smallest
294+
relation that contains \idr{r} and that is both reflexive and transitive.
295+
Formally, it is defined like this in the Relations module of the Idris standard
296+
library:
297+
298+
> data Clos_refl_trans : (r : Relation t) -> Relation t where
299+
> Rt_step : r x y -> Clos_refl_trans r x y
300+
> Rt_refl : Clos_refl_trans r x x
301+
> Rt_trans : Clos_refl_trans r x y -> Clos_refl_trans r y z ->
302+
> Clos_refl_trans r x z
303+
304+
For example, the reflexive and transitive closure of the \idr{Next_nat} relation
305+
coincides with the \idr{Le} relation.
306+
307+
\todo[inline]{Copied `<->` for now}
308+
309+
> iff : {p,q : Type} -> Type
310+
> iff {p} {q} = (p -> q, q -> p)
311+
>
312+
> syntax [p] "<->" [q] = iff {p} {q}
313+
314+
> next_nat_closure_is_le : (n <=' m) <-> (Clos_refl_trans Next_nat n m)
315+
> next_nat_closure_is_le = (to, fro)
316+
> where
317+
> to : Le n m -> Clos_refl_trans Next_nat n m
318+
> to Le_n = Rt_refl
319+
> to (Le_S {m} le) = Rt_trans {y=m} (to le) (Rt_step NN)
320+
> fro : Clos_refl_trans Next_nat n m -> Le n m
321+
> fro (Rt_step NN) = Le_S Le_n
322+
> fro Rt_refl = Le_n
323+
> fro (Rt_trans {x=n} {y} {z=m} ny ym) =
324+
> le_trans n y m (fro ny) (fro ym)
325+
326+
The above definition of reflexive, transitive closure is natural: it says,
327+
explicitly, that the reflexive and transitive closure of \idr{r} is the least
328+
relation that includes \idr{r} and that is closed under rules of reflexivity and
329+
transitivity. But it turns out that this definition is not very convenient for
330+
doing proofs, since the "nondeterminism" of the \idr{Rt_trans} rule can
331+
sometimes lead to tricky inductions. Here is a more useful definition:
332+
333+
> data Clos_refl_trans_1n : (r : Relation t) -> (x : t) -> t -> Type where
334+
> Rt1n_refl : Clos_refl_trans_1n r x x
335+
> Rt1n_trans : r x y -> Clos_refl_trans_1n r y z -> Clos_refl_trans_1n r x z
336+
337+
\todo[inline]{Edit}
338+
339+
Our new definition of reflexive, transitive closure "bundles" the \idr{Rt_step}
340+
and \idr{Rt_trans} rules into the single rule step. The left-hand premise of
341+
this step is a single use of \idr{r}, leading to a much simpler induction
342+
principle.
343+
344+
Before we go on, we should check that the two definitions do indeed define the
345+
same relation...
346+
347+
First, we prove two lemmas showing that \idr{Clos_refl_trans_1n} mimics the
348+
behavior of the two "missing" \idr{Clos_refl_trans} constructors.
349+
350+
> rsc_R : r x y -> Clos_refl_trans_1n r x y
351+
> rsc_R rxy = Rt1n_trans rxy Rt1n_refl
352+
353+
354+
==== Exercise: 2 stars, optional (rsc_trans)
355+
356+
> rsc_trans : Clos_refl_trans_1n r x y -> Clos_refl_trans_1n r y z ->
357+
> Clos_refl_trans_1n r x z
358+
> rsc_trans crxy cryz = ?rsc_trans_rhs
359+
360+
$\square$
361+
362+
Then we use these facts to prove that the two definitions of reflexive,
363+
transitive closure do indeed define the same relation.
364+
365+
366+
==== Exercise: 3 stars, optional (rtc_rsc_coincide)
367+
368+
> rtc_rsc_coincide : (Clos_refl_trans r x y) <-> (Clos_refl_trans_1n r x y)
369+
> rtc_rsc_coincide = ?rtc_rsc_coincide_rhs
370+
371+
$\square$

0 commit comments

Comments
 (0)