]> matita.cs.unibo.it Git - helm.git/blob - weblib/tutorial/chapter5.ma
commit by user andrea
[helm.git] / weblib / tutorial / chapter5.ma
1 (* The fact of being able to decide, via a computable boolean function, the 
2 equality between elements of a given set is an essential prerequisite for 
3 effectively searching an element of that set inside a data structure. In this 
4 section we shall define several boolean functions acting on lists of elements in 
5 a DeqSet, and prove some of their properties.*)
6
7 include "basics/list.ma".
8 include "tutorial/chapter4.ma".
9
10 (* The first function we define is an effective version of the membership relation,
11 between an element x and a list l. Its definition is a straightforward recursion on
12 l.*)
13
14 let rec memb (S:DeqSet) (x:S) (l: list\ 5span class="error" title="Parse error: RPAREN expected after [term] (in [arg])"\ 6\ 5/span\ 6 S) on l  ≝
15   match l with
16   [ nil ⇒ false
17   | cons a tl ⇒ (x =\ 5span class="error" title="Parse error: NUMBER '1' or [term] or [sym=] expected after [sym=] (in [term])"\ 6\ 5/span\ 6= a) ∨ memb S x tl
18   ].
19
20 notation < "\memb x l" non associative with precedence 90 for @{'memb $x $l}.
21 interpretation "boolean membership" 'memb a l = (memb ? a l).
22
23 (* We can now prove several interesing properties for memb:
24 - memb_hd: x is a member of x::l
25 - memb_cons: if x is a member of l than x is a member of a::l
26 - memb_single: if x is a member of [a] then x=a
27 - memb_append: if x is a member of l1@l2 then either x is a member of l1
28   or x is a member of l2
29 - memb_append_l1: if x is a member of l1 then x is a member of l1@l2
30 - memb_append_l2: if x is a member of l2 then x is a member of l1@l2
31 - memb_exists: if x is a member of l, than l can decomposed as l1@(x::l2)
32 - not_memb_to_not_eq: if x is not a member of l and y is, then x≠y
33 - memb_map: if a is a member of l, then (f a) is a member of (map f l)
34 - memb_compose: if a is a member of l1 and b is a meber of l2 than
35   (op a b) is a member of (compose op l1 l2)
36 *)
37
38 lemma memb_hd: ∀S,a,l. memb S a (a::l) = true.
39 #S #a #l normalize >(proj2 … (eqb_true S …) (refl S a)) //
40 qed.
41
42 lemma memb_cons: ∀S,a,b,l. 
43   memb S a l = true → memb\ 5a href="cic:/matita/tutorial/chapter5/memb.fix(0,2,4)"\ 6\ 5/a\ 6 S a (b::l) = true.
44 #S #a #b #l normalize cases (a==b) normalize // 
45 qed.
46
47 lemma memb_single: ∀S,a,x. memb S a (x::[]) = true → a = x.
48 #S #a #x normalize cases (true_or_false … (a==x)) #H
49   [#_ >(\P H) // |>H normalize #abs @False_ind /\ 5span class="autotactic"\ 62\ 5span class="autotrace"\ 6 trace absurd\ 5/span\ 6\ 5/span\ 6/]
50 qed.
51
52 lemma memb_append: ∀S,a,l1,l2. 
53 memb S a (l1@\ 5a title="append" href="cic:/fakeuri.def(1)"\ 6\ 5/a\ 6l2) = true → memb S a l1= true ∨ memb S a l2 = true.
54 #S #a #l1 elim l1 normalize [#l2 #H %2 //] 
55 #b #tl #Hind #l2 cases (a==b) normalize /\ 5span class="autotactic"\ 62\ 5span class="autotrace"\ 6 trace orb_true_l\ 5/span\ 6\ 5/span\ 6
56 qed. 
57
58 lemma memb_append_l1: ∀S,a,l1,l2. 
59  memb S a l1= true → memb S a (l1@\ 5a title="append" href="cic:/fakeuri.def(1)"\ 6\ 5/a\ 6l2) = true.
60 #S #a #l1 elim l1 normalize
61   [normalize #le #abs @False_ind /\ 5span class="autotactic"\ 62\ 5span class="autotrace"\ 6 trace absurd\ 5/span\ 6\ 5/span\ 6/
62   |#b #tl #Hind #l2 cases (a==b) normalize /\ 5span class="autotactic"\ 62\ 5span class="autotrace"\ 6 trace \ 5/span\ 6\ 5/span\ 6
63   ]
64 qed. 
65
66 lemma memb_append_l2: ∀S,a,l1,l2. 
67  memb S a l2= true → memb S a (l1@l2) = true.
68 #S #a #l1 elim l1 normalize //
69 #b #tl #Hind #l2 cases (a==b) normalize /\ 5span class="autotactic"\ 62\ 5span class="autotrace"\ 6 trace \ 5/span\ 6\ 5/span\ 6
70 qed. 
71
72 lemma memb_exists: ∀S,a,l.memb S a l = true\ 5a href="cic:/matita/basics/bool/bool.con(0,1,0)"\ 6\ 5/a\ 6 → ∃l1,l2.l=l1@(a::l2).
73 #S #a #l elim l [normalize #abs @False_ind /\ 5span class="autotactic"\ 62\ 5span class="autotrace"\ 6 trace absurd\ 5/span\ 6\ 5/span\ 6/]
74 #b #tl #Hind #H cases (orb_true_l … H)
75   [#eqba @(ex_intro … (nil S)) @(ex_intro … tl) >(\P eqba) //
76   |#mem_tl cases (Hind mem_tl) #l1 * #l2 #eqtl
77    @(ex_intro … (b::l1)) @(ex_intro … l2) >eqtl //
78   ]
79 qed.
80
81 lemma not_memb_to_not_eq: ∀S,a,b,l. 
82  memb S a l = false\ 5a href="cic:/matita/basics/bool/bool.con(0,2,0)"\ 6\ 5/a\ 6 → memb S b l = true → a==b = false.
83 #S #a #b #l cases (true_or_false (a==b)) // 
84 #eqab >(\P eqab) #H >H #abs @False_ind /\ 5span class="autotactic"\ 62\ 5span class="autotrace"\ 6 trace absurd\ 5/span\ 6\ 5/span\ 6/
85 qed. 
86  
87 lemma memb_map: ∀S1,S2,f,a,l. memb S1 a l= true → 
88   memb S2 (f a) (map … f l) =\ 5a title="leibnitz's equality" href="cic:/fakeuri.def(1)"\ 6\ 5/a\ 6 true.
89 #S1 #S2 #f #a #l elim l normalize [//]
90 #x #tl #memba cases (true_or_false (a==x))
91   [#eqx >eqx >(\P eqx) >(\b (refl … (f x))) normalize //
92   |#eqx >eqx cases (f a==f x) normalize /\ 5span class="autotactic"\ 62\ 5span class="autotrace"\ 6 trace \ 5/span\ 6\ 5/span\ 6/
93   ]
94 qed.
95
96 lemma memb_compose: ∀S1,S2,S3,op,a1,a2,l1,l2.   
97   memb S1 a1 l1 = true → memb S2 a2 l2 = true →
98   memb S3 (op a1 a2) (compose S1 S2 S3 op l1 l2) = true.
99 #S1 #S2 #S3 #op #a1 #a2 #l1 elim l1 [normalize //]
100 #x #tl #Hind #l2 #memba1 #memba2 cases (orb_true_l\ 5a href="cic:/matita/basics/bool/orb_true_l.def(2)"\ 6\ 5/a\ 6 … memba1)
101   [#eqa1 >(\P eqa1) @memb_append_l1 @memb_map // 
102   |#membtl @memb_append_l2 @Hind //
103   ]
104 qed.
105
106 (* If we are interested in representing finite sets as lists, is is convenient
107 to avoid duplications of elements. The following uniqueb check this property. *)
108
109 (*************** unicity test *****************)
110
111 let rec uniqueb (S:DeqSet) l on l : bool ≝
112   match l with 
113   [ nil ⇒ true
114   | cons a tl ⇒ notb (memb S a tl) ∧ uniqueb S tl
115   ].
116
117 (* unique_append l1 l2 add l1 in fornt of l2, but preserving unicity *)
118
119 let rec unique_append (S:DeqSet) (l1,l2: list S) on l1 ≝
120   match l1 with
121   [ nil ⇒ l2
122   | cons a tl ⇒ 
123      let r ≝ unique_append S tl l2 in
124      if memb S a r then r else a::r
125   ].
126
127 axiom unique_append_elim: ∀S:DeqSet.∀P: S → Prop.∀l1,l2. 
128 (∀x. memb S x l1 =\ 5a title="leibnitz's equality" href="cic:/fakeuri.def(1)"\ 6\ 5/a\ 6 true → P x) → (∀x. memb S x l2 = true → P x) →
129 ∀x. memb S x (unique_append S l1 l2) = true → P x. 
130
131 lemma unique_append_unique: ∀S,l1,l2. uniqueb S l2 = true →
132   uniqueb S (unique_append S l1 l2) = true.
133 #S #l1 elim l1 normalize // #a #tl #Hind #l2 #uniquel2
134 cases (true_or_false\ 5a href="cic:/matita/basics/bool/true_or_false.def(1)"\ 6\ 5/a\ 6 … (memb S a (unique_append S tl l2))) 
135 #H >H normalize [@Hind //] >H normalize @Hind //
136 qed.
137
138 (******************* sublist *******************)
139 definition sublist ≝ 
140   λS,l1,l2.∀a. memb S a l1 = true → memb S a l2 = true.
141
142 lemma sublist_length: ∀S,l1,l2. 
143  uniqueb S l1 = true → sublist S l1 l2 → |l1| ≤ |l2|.
144 #S #l1 elim l1 // 
145 #a #tl #Hind #l2 #unique #sub
146 cut (∃\ 5a title="exists" href="cic:/fakeuri.def(1)"\ 6\ 5/a\ 6l3,l4.l2=l3@(a::l4)) [@memb_exists @sub //]
147 * #l3 * #l4 #eql2 >eql2 >length_append normalize 
148 applyS le_S_S <length_append @Hind [@(andb_true_r … unique)]
149 >eql2 in sub; #sub #x #membx 
150 cases (memb_append … (sub x (orb_true_r2 … membx)))
151   [#membxl3 @memb_append_l1 //
152   |#membxal4 cases (orb_true_l … membxal4)
153     [#eqxa @False_ind lapply (andb_true_l … unique)
154      <(\P eqxa) >membx normalize /\ 5span class="autotactic"\ 62\ 5span class="autotrace"\ 6 trace absurd\ 5/span\ 6\ 5/span\ 6/ |#membxl4 @memb_append_l2\ 5a href="cic:/matita/tutorial/chapter5/memb_append_l2.def(5)"\ 6\ 5/a\ 6 //
155     ]
156   ]
157 qed.
158
159 lemma sublist_unique_append_l1: 
160   ∀S,l1,l2. sublist S l1 (unique_append S l1 l2).
161 #S #l1 elim l1 normalize [#l2 #S #abs @False_ind /\ 5span class="autotactic"\ 62\ 5span class="autotrace"\ 6 trace absurd\ 5/span\ 6\ 5/span\ 6/]
162 #x #tl #Hind #l2 #a 
163 normalize cases (true_or_false … (a==x)) #eqax >eqax 
164 [<(\P eqax) cases (true_or_false (memb S a (unique_append S tl l2)))
165   [#H >H normalize // | #H >H normalize >(\b (refl … a)) //]
166 |cases (memb S x (unique_append S tl l2)) normalize 
167   [/\ 5span class="autotactic"\ 62\ 5span class="autotrace"\ 6 trace \ 5/span\ 6\ 5/span\ 6/ |>eqax normalize /\ 5span class="autotactic"\ 62\ 5span class="autotrace"\ 6 trace \ 5/span\ 6\ 5/span\ 6/]
168 ]
169 qed.
170
171 lemma sublist_unique_append_l2: 
172   ∀S,l1,l2. sublist S l2 (unique_append S l1 l2).
173 #S #l1 elim l1 [normalize //] #x #tl #Hind normalize 
174 #l2 #a cases (memb S x (unique_append\ 5a href="cic:/matita/tutorial/chapter5/unique_append.fix(0,1,5)"\ 6\ 5/a\ 6 S tl l2)) normalize
175 [@Hind | cases (a==x) normalize // @Hind]
176 qed.
177
178 lemma decidable_sublist:∀S,l1,l2. 
179   (sublist S l1 l2) ∨ ¬(sublist S l1 l2).
180 #S #l1 #l2 elim l1 
181   [%1 #a normalize in ⊢ (%→?); #abs @False_ind /\ 5span class="autotactic"\ 62\ 5span class="autotrace"\ 6 trace absurd\ 5/span\ 6\ 5/span\ 6/
182   |#a #tl * #subtl 
183     [cases (true_or_false (memb S a l2)) #memba
184       [%1 whd #x #membx cases (orb_true_l … membx)
185         [#eqax >(\P eqax) // |@subtl]
186       |%2 @(not_to_not … (eqnot_to_noteq … true memba)) #H1 @H1 @memb_hd
187       ]
188     |%2 @(not_to_not … subtl) #H1 #x #H2 @H1 @memb_cons\ 5a href="cic:/matita/tutorial/chapter5/memb_cons.def(5)"\ 6\ 5/a\ 6 //
189     ] 
190   ]
191 qed.
192
193 (********************* filtering *****************)
194
195 lemma filter_true: ∀S,f,a,l. 
196   memb S a (filter S f l) = true → f a = true.
197 #S #f #a #l elim l [normalize #H @False_ind /\ 5span class="autotactic"\ 62\ 5span class="autotrace"\ 6 trace absurd\ 5/span\ 6\ 5/span\ 6/]
198 #b #tl #Hind cases (true_or_false (f b)) #H
199 normalize >H normalize [2:@Hind]
200 cases (true_or_false (a==b)) #eqab
201   [#_ >(\P eqab) // | >eqab normalize @Hind]
202 qed. 
203   
204 lemma memb_filter_memb: ∀S,f,a,l. 
205   memb S a (filter S f l) = true → memb\ 5a href="cic:/matita/tutorial/chapter5/memb.fix(0,2,4)"\ 6\ 5/a\ 6 S a l = true.
206 #S #f #a #l elim l [normalize //]
207 #b #tl #Hind normalize (cases (f b)) normalize 
208 cases (a==b) normalize // @Hind
209 qed.
210   
211 lemma memb_filter: ∀S,f,l,x. memb S x (filter ? f l) = true → 
212 memb S x l = true ∧ (f x = true).
213 /\ 5span class="autotactic"\ 63\ 5span class="autotrace"\ 6 trace conj, filter_true, memb_filter_memb\ 5a href="cic:/matita/tutorial/chapter5/memb_filter_memb.def(5)"\ 6\ 5/a\ 6\ 5/span\ 6\ 5/span\ 6/ qed.
214
215 lemma memb_filter_l: ∀S,f,x,l. (f x = true) → memb S x l = true →
216 memb S x (filter ? f l) = true.
217 #S #f #x #l #fx elim l normalize //
218 #b #tl #Hind cases (true_or_false (x==b)) #eqxb
219   [<(\P eqxb) >(\b (refl … x)) >fx normalize >(\b (refl … x)) normalize //
220   |>eqxb cases (f b) normalize [>eqxb normalize @Hind| @Hind]
221   ]
222 qed. 
223
224 (********************* exists *****************)
225
226 let rec exists (A:Type[0]) (p:A → bool) (l:list A) on l : bool\ 5a href="cic:/matita/basics/bool/bool.ind(1,0,0)"\ 6\ 5/a\ 6 ≝
227 match l with
228 [ nil ⇒ false
229 | cons h t ⇒ orb (p h) (exists A p t)
230 ].