]> matita.cs.unibo.it Git - helm.git/blob - matita/matita/lib/turing/universal/uni_step.ma
New version of init copy
[helm.git] / matita / matita / lib / turing / universal / uni_step.ma
1 (*
2     ||M||  This file is part of HELM, an Hypertextual, Electronic   
3     ||A||  Library of Mathematics, developed at the Computer Science 
4     ||T||  Department of the University of Bologna, Italy.           
5     ||I||                                                            
6     ||T||  
7     ||A||  
8     \   /  This file is distributed under the terms of the       
9      \ /   GNU General Public License Version 2   
10       V_____________________________________________________________*)
11
12
13 (* COMPARE BIT
14
15 *)
16
17 include "turing/universal/copy.ma".
18
19 (*
20
21 step :
22
23 if is_true(current) (* current state is final *)
24    then nop
25    else 
26    (* init_match *)
27    mark;
28    adv_to_grid_r;
29    move_r;
30    mark;
31    move_l;
32    adv_to_mark_l
33    (* /init_match *)
34    match_tuple;
35    if is_marked(current) = false (* match ok *)
36       then 
37            (* init_copy *)
38            move_l;
39            init_current;
40            move_r;
41            adv_to_mark_r;
42            adv_mark_r;
43            (* /init_copy *)
44            copy;
45            move_r;
46            (* move_tape *)
47            by cases on current: 
48              case bit false: move_tape_l
49              case bit true: move_tape_r
50              case null: adv_to_grid_l; move_l; adv_to_grid_l;
51            move_r;
52            (* /move_tape *)
53       else sink;
54         
55 *)
56
57 definition init_match ≝ 
58   seq ? (mark ?) 
59     (seq ? (adv_to_mark_r ? (λc:STape.is_grid (\fst c)))
60       (seq ? (move_r ?) 
61         (seq ? (mark ?)
62           (seq ? (move_l ?) 
63             (adv_to_mark_l ? (is_marked ?)))))).
64             
65 definition R_init_match ≝ λt1,t2.
66   ∀ls,l,rs,c,d. no_grids (〈c,false〉::l) → no_marks l → 
67   t1 = midtape STape ls 〈c,false〉 (l@〈grid,false〉::〈d,false〉::rs) →
68   t2 = midtape STape ls 〈c,true〉 (l@〈grid,false〉::〈d,true〉::rs).
69   
70 lemma sem_init_match : Realize ? init_match R_init_match.
71 #intape 
72 cases (sem_seq ????? (sem_mark ?)
73        (sem_seq ????? (sem_adv_to_mark_r ? (λc:STape.is_grid (\fst c)))
74         (sem_seq ????? (sem_move_r ?)
75          (sem_seq ????? (sem_mark ?)
76           (sem_seq ????? (sem_move_l ?)
77            (sem_adv_to_mark_l ? (is_marked ?)))))) intape)
78 #k * #outc * #Hloop #HR 
79 @(ex_intro ?? k) @(ex_intro ?? outc) % [@Hloop] -Hloop
80 #ls #l #rs #c #d #Hnogrids #Hnomarks #Hintape
81 cases HR -HR
82 #ta * whd in ⊢ (%→?); #Hta lapply (Hta … Hintape) -Hta -Hintape #Hta
83 * #tb * whd in ⊢ (%→?); #Htb cases (Htb … Hta) -Htb -Hta 
84   [* #Hgridc @False_ind @(absurd … Hgridc) @eqnot_to_noteq 
85    @(Hnogrids 〈c,false〉) @memb_hd ]
86 * #Hgrdic #Htb lapply (Htb l 〈grid,false〉 (〈d,false〉::rs) (refl …) (refl …) ?) 
87   [#x #membl @Hnogrids @memb_cons @membl] -Htb #Htb
88 * #tc * whd in ⊢ (%→?); #Htc lapply (Htc … Htb) -Htc -Htb #Htc
89 * #td * whd in ⊢ (%→?); #Htd lapply (Htd … Htc) -Htd -Htc #Htd
90 * #te * whd in ⊢ (%→?); #Hte lapply (Hte … Htd) -Hte -Htd #Hte
91 whd in ⊢ (%→?); #Htf cases (Htf … Hte) -Htf -Hte 
92   [* whd in ⊢ ((??%?)→?); #Habs destruct (Habs)]
93 * #_ #Htf lapply (Htf (reverse ? l) 〈c,true〉 ls (refl …) (refl …) ?) 
94   [#x #membl @Hnomarks @daemon] -Htf #Htf >Htf >reverse_reverse %
95 qed.
96
97
98 (* init_copy 
99
100            init_current_on_match; (* no marks in current *)
101            move_r;
102            adv_to_mark_r;
103            adv_mark_r;
104
105 *)
106
107 definition init_copy ≝ 
108   seq ? init_current_on_match
109     (seq ? (move_r ?) 
110       (seq ? (adv_to_mark_r ? (is_marked ?))
111         (adv_mark_r ?))).
112
113 definition R_init_copy ≝ λt1,t2.
114   ∀l1,l2,c,ls,d,rs. 
115   no_marks l1 → no_grids l1 → 
116   no_marks l2 → is_grid c = false → 
117   t1 = midtape STape (l1@〈c,false〉::〈grid,false〉::ls) 〈grid,false〉 (l2@〈comma,true〉::〈d,false〉::rs) → 
118   t2 = midtape STape (〈comma,false〉::(reverse ? l2)@〈grid,false〉::l1@〈c,true〉::〈grid,false〉::ls) 〈d,true〉 rs.
119
120 lemma list_last: ∀A.∀l:list A.
121   l = [ ] ∨ ∃a,l1. l = l1@[a].
122 #A #l <(reverse_reverse ? l) cases (reverse A l)
123   [%1 //
124   |#a #l1 %2 @(ex_intro ?? a) @(ex_intro ?? (reverse ? l1)) //
125   ]
126 qed.
127    
128 lemma sem_init_copy : Realize ? init_copy R_init_copy.
129 #intape 
130 cases (sem_seq ????? sem_init_current_on_match
131         (sem_seq ????? (sem_move_r ?)
132           (sem_seq ????? (sem_adv_to_mark_r ? (is_marked ?))
133             (sem_adv_mark_r ?))) intape)
134 #k * #outc * #Hloop #HR 
135 @(ex_intro ?? k) @(ex_intro ?? outc) % [@Hloop] -Hloop
136 #l1 #l2 #c #ls #d #rs #Hl1marks #Hl1grids #Hl2marks #Hc #Hintape
137 cases HR -HR
138 #ta * whd in ⊢ (%→?); #Hta lapply (Hta … Hl1grids Hc Hintape) -Hta -Hintape #Hta
139 * #tb * whd in ⊢ (%→?); #Htb lapply (Htb  … Hta) -Htb -Hta
140 generalize in match Hl1marks; -Hl1marks cases (list_last ? l1) 
141   [#eql1 >eql1 #Hl1marks whd in ⊢ ((???%)→?); whd in ⊢ ((???(????%))→?); #Htb
142    * #tc * whd in ⊢ (%→?); #Htc lapply (Htc  … Htb) -Htc -Htb *
143     [* whd in ⊢ ((??%?)→?); #Htemp destruct (Htemp)]
144    * #_ #Htc lapply (Htc … (refl …) (refl …) ?)
145     [#x #membx @Hl2marks @membx]
146    #Htc whd in ⊢ (%→?); #Houtc lapply (Houtc … Htc) -Houtc -Htc #Houtc
147    >Houtc %
148   |* #c1 * #tl #eql1 >eql1 #Hl1marks >reverse_append >reverse_single 
149    whd in ⊢ ((???%)→?); whd in ⊢ ((???(????%))→?);
150    >associative_append whd in ⊢ ((???(????%))→?); #Htb
151    * #tc * whd in ⊢ (%→?); #Htc lapply (Htc  … Htb) -Htc -Htb *
152     [* >Hl1marks [#Htemp destruct (Htemp)] @memb_append_l2 @memb_hd]
153    * #_ >append_cons <associative_append #Htc lapply (Htc … (refl …) (refl …) ?)
154     [#x #membx cases (memb_append … membx) -membx #membx
155       [cases (memb_append … membx) -membx #membx
156         [@Hl1marks @memb_append_l1 @daemon
157         |>(memb_single … membx) %
158         ]
159       |@Hl2marks @membx
160       ]]
161   #Htc whd in ⊢ (%→?); #Houtc lapply (Houtc … Htc) -Houtc -Htc #Houtc
162   >Houtc >reverse_append >reverse_append >reverse_single 
163   >reverse_reverse >associative_append >associative_append 
164   >associative_append %
165 qed.
166   
167 (* OLD 
168 definition init_copy ≝ 
169   seq ? (adv_mark_r ?) 
170     (seq ? init_current_on_match
171       (seq ? (move_r ?) 
172         (adv_to_mark_r ? (is_marked ?)))).
173
174 definition R_init_copy ≝ λt1,t2.
175   ∀l1,l2,c,l3,d,rs. 
176   no_marks l1 → no_grids l1 → 
177   no_marks l2 → no_grids l2 → is_grid c = false → is_grid d =false →
178   t1 = midtape STape (l1@〈grid,false〉::l2@〈c,false〉::〈grid,false〉::l3) 〈comma,true〉 (〈d,false〉::rs) → 
179   t2 = midtape STape (〈comma,false〉::l1@〈grid,false〉::l2@〈c,true〉::〈grid,false〉::l3) 〈d,true〉 rs.
180
181 lemma list_last: ∀A.∀l:list A.
182   l = [ ] ∨ ∃a,l1. l = l1@[a].
183 #A #l <(reverse_reverse ? l) cases (reverse A l)
184   [%1 //
185   |#a #l1 %2 @(ex_intro ?? a) @(ex_intro ?? (reverse ? l1)) //
186   ]
187 qed.
188    
189 lemma sem_init_copy : Realize ? init_copy R_init_copy.
190 #intape 
191 cases (sem_seq ????? (sem_adv_mark_r ?)
192        (sem_seq ????? sem_init_current_on_match
193         (sem_seq ????? (sem_move_r ?)
194          (sem_adv_to_mark_r ? (is_marked ?)))) intape)
195 #k * #outc * #Hloop #HR 
196 @(ex_intro ?? k) @(ex_intro ?? outc) % [@Hloop] -Hloop
197 #l1 #l2 #c #l3 #d #rs #Hl1marks #Hl1grids #Hl2marks #Hl2grids #Hc #Hd #Hintape
198 cases HR -HR
199 #ta * whd in ⊢ (%→?); #Hta lapply (Hta … Hintape) -Hta -Hintape #Hta
200 * #tb * whd in ⊢ (%→?); 
201 >append_cons #Htb lapply (Htb (〈comma,false〉::l1) l2 c … Hta) 
202   [@Hd |@Hc |@Hl2grids 
203    |#x #membx cases (orb_true_l … membx) -membx #membx 
204      [>(\P membx) // | @Hl1grids @membx]
205   ] -Htb #Htb
206 * #tc * whd in ⊢ (%→?); #Htc lapply (Htc … Htb) -Htc -Htb
207 >reverse_append >reverse_cons cases (list_last ? l2)
208   [#Hl2 >Hl2 >associative_append whd in ⊢ ((???(??%%%))→?); #Htc
209    whd in ⊢ (%→?); #Htd cases (Htd … Htc) -Htd -Htc
210     [* whd in ⊢ ((??%?)→?); #Habs destruct (Habs)]
211    * #_ #Htf lapply (Htf … (refl …) (refl …) ?) 
212     [#x >reverse_cons #membx cases (memb_append … membx) -membx #membx
213       [@Hl1marks @daemon |>(memb_single … membx) //] 
214     -Htf
215     |#Htf >Htf >reverse_reverse >associative_append %
216     ]
217   |* #a * #l21 #Heq >Heq >reverse_append >reverse_single 
218    >associative_append >associative_append >associative_append whd in ⊢ ((???(??%%%))→?); #Htc
219    whd in ⊢ (%→?); #Htd cases (Htd … Htc) -Htd -Htc
220     [* >Hl2marks [#Habs destruct (Habs) |>Heq @memb_append_l2 @memb_hd]]
221    * #_ <associative_append <associative_append #Htf lapply (Htf … (refl …) (refl …) ?) 
222     [#x >reverse_cons #membx cases (memb_append … membx) -membx #membx
223       [cases (memb_append … membx) -membx #membx
224         [@Hl2marks >Heq @memb_append_l1 @daemon
225         |>(memb_single … membx) //]
226       |cases (memb_append … membx) -membx #membx
227         [@Hl1marks @daemon |>(memb_single … membx) //]
228       ]
229     | #Htf >Htf >reverse_append >reverse_reverse
230       >reverse_append >reverse_reverse >associative_append 
231       >reverse_single >associative_append >associative_append 
232       >associative_append % 
233     ]
234   ]
235 qed. *)
236
237 include "turing/universal/move_tape.ma".
238
239 definition exec_move ≝ 
240   seq ? (adv_to_mark_r … (is_marked ?))
241     (seq ? init_copy
242       (seq ? copy
243         (seq ? (move_r …)
244           (seq ? move_tape (move_r …))))).
245
246 definition lift_tape ≝ λls,c,rs.
247   let 〈c0,b〉 ≝ c in
248   let c' ≝ match c0 with
249   [ null ⇒ None ?
250   | _ ⇒ Some ? c ]
251   in
252   mk_tape STape ls c' rs.
253   
254 definition sim_current_of_tape ≝ λt.
255   match current STape t with
256   [ None ⇒ 〈null,false〉
257   | Some c0 ⇒ c0 ].
258
259 (*
260  t1 =  ls # cs c # table # rs  
261  
262  let simt ≝ lift_tape ls c rs in
263  let simt' ≝ move_left simt' in
264  
265  t2 = left simt'# cs (sim_current_of_tape simt') # table # right simt'
266 *)
267           
268 (*
269 definition R_move
270
271 definition R_exec_move ≝ λt1,t2.
272   ∀ls,current,table1,newcurrent,table2,rs.
273   t1 = midtape STape (current@〈grid,false〉::ls) 〈grid,false〉
274        (table1@〈comma,true〉::newcurrent@〈comma,false〉::move::table2@
275         〈grid,false〉::rs) → 
276   table_TM (table1@〈comma,false〉::newcurrent@〈comma,false〉::move::table2) →
277   t2 = midtape
278 *)
279
280 (*
281
282 step :
283
284 if is_true(current) (* current state is final *)
285    then nop
286    else 
287    init_match;
288    match_tuple;
289    if is_marked(current) = false (* match ok *)
290       then exec_move; 
291       else sink;
292         
293 *)
294
295 definition mk_tuple ≝ λc,newc,mv.
296   c @ 〈comma,false〉:: newc @ 〈comma,false〉 :: [〈mv,false〉].
297
298 inductive match_in_table (c,newc:list STape) (mv:unialpha) : list STape → Prop ≝ 
299 | mit_hd : 
300    ∀tb.
301    match_in_table c newc mv (mk_tuple c newc mv@〈bar,false〉::tb)
302 | mit_tl :
303    ∀c0,newc0,mv0,tb.
304    match_in_table c newc mv tb → 
305    match_in_table c newc mv (mk_tuple c0 newc0 mv0@〈bar,false〉::tb).
306
307 definition move_of_unialpha ≝ 
308   λc.match c with
309   [ bit x ⇒ match x with [ true ⇒ R | false ⇒ L ]
310   | _ ⇒ N ].
311
312 definition R_uni_step ≝ λt1,t2.
313   ∀n,table,c,c1,ls,rs,curs,curc,news,newc,mv.
314   table_TM n table → 
315   match_in_table (〈c,false〉::curs@[〈curc,false〉]) 
316     (〈c1,false〉::news@[〈newc,false〉]) mv table → 
317   t1 = midtape STape (〈grid,false〉::ls) 〈c,false〉 
318     (curs@〈curc,false〉::〈grid,false〉::table@〈grid,false〉::rs) → 
319   ∀t1',ls1,rs1.t1' = lift_tape ls 〈curc,false〉 rs → 
320   (t2 = midtape STape (〈grid,false〉::ls1) 〈c1,false〉 
321     (news@〈newc,false〉::〈grid,false〉::table@〈grid,false〉::rs1) ∧
322    lift_tape ls1 〈newc,false〉 rs1 = 
323    tape_move STape t1' (Some ? 〈〈newc,false〉,move_of_unialpha mv〉)).
324
325 definition no_nulls ≝ 
326  λl:list STape.∀x.memb ? x l = true → is_null (\fst x) = false.
327  
328 definition R_move_tape_r_abstract ≝ λt1,t2.
329   ∀rs,n,table,curc,curconfig,ls.
330   bit_or_null curc = true → only_bits_or_nulls curconfig → table_TM n table → 
331   t1 = midtape STape (table@〈grid,false〉::〈curc,false〉::curconfig@〈grid,false〉::ls) 
332          〈grid,false〉 rs →
333   no_nulls rs → 
334   ∀t1'.t1' = lift_tape ls 〈curc,false〉 rs → 
335   ∃ls1,rs1,newc.
336   (t2 = midtape STape ls1 〈grid,false〉 (reverse ? curconfig@newc::
337     〈grid,false〉::reverse ? table@〈grid,false〉::rs1) ∧
338    lift_tape ls1 newc rs1 = 
339    tape_move_right STape ls 〈curc,false〉 rs).
340    
341 lemma lift_tape_not_null :
342   ∀ls,c,rs. is_null (\fst c) = false → 
343   lift_tape ls c rs = mk_tape STape ls (Some ? c) rs.
344 #ls * #c0 #bc0 #rs cases c0
345 [|normalize in ⊢ (%→?); #Hfalse destruct (Hfalse) ]
346 //
347 qed.
348  
349 lemma mtr_concrete_to_abstract :
350   ∀t1,t2.R_move_tape_r t1 t2 → R_move_tape_r_abstract t1 t2.
351 #t1 #t2 whd in ⊢(%→?); #Hconcrete
352 #rs #n #table #curc #curconfig #ls #Hcurc #Hcurconfig #Htable #Ht1
353 #Hrsnonulls #t1' #Ht1'
354 cases (Hconcrete … Htable Ht1) //
355 [ * #Hrs #Ht2
356   @(ex_intro ?? (〈curc,false〉::ls)) @(ex_intro ?? [])
357   @(ex_intro ?? 〈null,false〉) %
358   [ >Ht2 %
359   | >Hrs % ]
360 | * #r0 * #rs0 * #Hrs #Ht2 
361   @(ex_intro ?? (〈curc,false〉::ls)) @(ex_intro ?? rs0)
362   @(ex_intro ?? r0) %
363   [ >Ht2 %
364   | >Hrs >lift_tape_not_null
365     [ %
366     | @Hrsnonulls >Hrs @memb_hd ] ]
367 qed.