]> matita.cs.unibo.it Git - helm.git/blob - matita/matita/lib/turing/universal/uni_step.ma
Progress
[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 (* init_copy 
98
99            adv_mark_r;
100            init_current_on_match; (* no marks in current *)
101            move_r;
102            adv_to_mark_r;
103 *)
104      
105 definition init_copy ≝ 
106   seq ? (adv_mark_r ?) 
107     (seq ? init_current_on_match
108       (seq ? (move_r ?) 
109         (adv_to_mark_r ? (is_marked ?)))).
110
111 definition R_init_copy ≝ λt1,t2.
112   ∀l1,l2,c,l3,d,rs. 
113   no_marks l1 → no_grids l1 → 
114   no_marks l2 → no_grids l2 → is_grid c = false → is_grid d =false →
115   t1 = midtape STape (l1@〈grid,false〉::l2@〈c,false〉::〈grid,false〉::l3) 〈comma,true〉 (〈d,false〉::rs) → 
116   t2 = midtape STape (〈comma,false〉::l1@〈grid,false〉::l2@〈c,true〉::〈grid,false〉::l3) 〈d,true〉 rs.
117
118 lemma list_last: ∀A.∀l:list A.
119   l = [ ] ∨ ∃a,l1. l = l1@[a].
120 #A #l <(reverse_reverse ? l) cases (reverse A l)
121   [%1 //
122   |#a #l1 %2 @(ex_intro ?? a) @(ex_intro ?? (reverse ? l1)) //
123   ]
124 qed.
125    
126 lemma sem_init_copy : Realize ? init_copy R_init_copy.
127 #intape 
128 cases (sem_seq ????? (sem_adv_mark_r ?)
129        (sem_seq ????? sem_init_current_on_match
130         (sem_seq ????? (sem_move_r ?)
131          (sem_adv_to_mark_r ? (is_marked ?)))) intape)
132 #k * #outc * #Hloop #HR 
133 @(ex_intro ?? k) @(ex_intro ?? outc) % [@Hloop] -Hloop
134 #l1 #l2 #c #l3 #d #rs #Hl1marks #Hl1grids #Hl2marks #Hl2grids #Hc #Hd #Hintape
135 cases HR -HR
136 #ta * whd in ⊢ (%→?); #Hta lapply (Hta … Hintape) -Hta -Hintape #Hta
137 * #tb * whd in ⊢ (%→?); 
138 >append_cons #Htb lapply (Htb (〈comma,false〉::l1) l2 c … Hta) 
139   [@Hd |@Hc |@Hl2grids 
140    |#x #membx cases (orb_true_l … membx) -membx #membx 
141      [>(\P membx) // | @Hl1grids @membx]
142   ] -Htb #Htb
143 * #tc * whd in ⊢ (%→?); #Htc lapply (Htc … Htb) -Htc -Htb
144 >reverse_append >reverse_cons cases (list_last ? l2)
145   [#Hl2 >Hl2 >associative_append whd in ⊢ ((???(??%%%))→?); #Htc
146    whd in ⊢ (%→?); #Htd cases (Htd … Htc) -Htd -Htc
147     [* whd in ⊢ ((??%?)→?); #Habs destruct (Habs)]
148    * #_ #Htf lapply (Htf … (refl …) (refl …) ?) 
149     [#x >reverse_cons #membx cases (memb_append … membx) -membx #membx
150       [@Hl1marks @daemon |>(memb_single … membx) //] 
151     -Htf
152     |#Htf >Htf >reverse_reverse >associative_append %
153     ]
154   |* #a * #l21 #Heq >Heq >reverse_append >reverse_single 
155    >associative_append >associative_append >associative_append whd in ⊢ ((???(??%%%))→?); #Htc
156    whd in ⊢ (%→?); #Htd cases (Htd … Htc) -Htd -Htc
157     [* >Hl2marks [#Habs destruct (Habs) |>Heq @memb_append_l2 @memb_hd]]
158    * #_ <associative_append <associative_append #Htf lapply (Htf … (refl …) (refl …) ?) 
159     [#x >reverse_cons #membx cases (memb_append … membx) -membx #membx
160       [cases (memb_append … membx) -membx #membx
161         [@Hl2marks >Heq @memb_append_l1 @daemon
162         |>(memb_single … membx) //]
163       |cases (memb_append … membx) -membx #membx
164         [@Hl1marks @daemon |>(memb_single … membx) //]
165       ]
166     | #Htf >Htf >reverse_append >reverse_reverse
167       >reverse_append >reverse_reverse >associative_append 
168       >reverse_single >associative_append >associative_append 
169       >associative_append % 
170     ]
171   ]
172 qed.
173
174 include "turing/universal/move_tape.ma".
175
176 definition exec_move ≝ 
177   seq ? (adv_to_mark_r … (is_marked ?))
178     (seq ? init_copy
179       (seq ? copy
180         (seq ? (move_r …)
181           (seq ? move_tape (move_r …))))).
182
183 definition lift_tape ≝ λls,c,rs.
184   let 〈c0,b〉 ≝ c in
185   let c' ≝ match c0 with
186   [ null ⇒ None ?
187   | _ ⇒ Some ? c ]
188   in
189   mk_tape STape ls c' rs.
190   
191 definition sim_current_of_tape ≝ λt.
192   match current STape t with
193   [ None ⇒ 〈null,false〉
194   | Some c0 ⇒ c0 ].
195
196 (*
197  t1 =  ls # cs c # table # rs  
198  
199  let simt ≝ lift_tape ls c rs in
200  let simt' ≝ move_left simt' in
201  
202  t2 = left simt'# cs (sim_current_of_tape simt') # table # right simt'
203 *)
204           
205 (*
206 definition R_move
207
208 definition R_exec_move ≝ λt1,t2.
209   ∀ls,current,table1,newcurrent,table2,rs.
210   t1 = midtape STape (current@〈grid,false〉::ls) 〈grid,false〉
211        (table1@〈comma,true〉::newcurrent@〈comma,false〉::move::table2@
212         〈grid,false〉::rs) → 
213   table_TM (table1@〈comma,false〉::newcurrent@〈comma,false〉::move::table2) →
214   t2 = midtape
215 *)
216
217 (*
218
219 step :
220
221 if is_true(current) (* current state is final *)
222    then nop
223    else 
224    init_match;
225    match_tuple;
226    if is_marked(current) = false (* match ok *)
227       then exec_move; 
228       else sink;
229         
230 *)
231
232 definition mk_tuple ≝ λc,newc,mv.
233   c @ 〈comma,false〉:: newc @ 〈comma,false〉 :: [〈mv,false〉].
234
235 inductive match_in_table (c,newc:list STape) (mv:unialpha) : list STape → Prop ≝ 
236 | mit_hd : 
237    ∀tb.
238    match_in_table c newc mv (mk_tuple c newc mv@〈bar,false〉::tb)
239 | mit_tl :
240    ∀c0,newc0,mv0,tb.
241    match_in_table c newc mv tb → 
242    match_in_table c newc mv (mk_tuple c0 newc0 mv0@〈bar,false〉::tb).
243
244 definition move_of_unialpha ≝ 
245   λc.match c with
246   [ bit x ⇒ match x with [ true ⇒ R | false ⇒ L ]
247   | _ ⇒ N ].
248
249 definition R_uni_step ≝ λt1,t2.
250   ∀n,table,c,c1,ls,rs,curs,curc,news,newc,mv.
251   table_TM n table → 
252   match_in_table (〈c,false〉::curs@[〈curc,false〉]) 
253     (〈c1,false〉::news@[〈newc,false〉]) mv table → 
254   t1 = midtape STape (〈grid,false〉::ls) 〈c,false〉 
255     (curs@〈curc,false〉::〈grid,false〉::table@〈grid,false〉::rs) → 
256   ∀t1',ls1,rs1.t1' = lift_tape ls 〈curc,false〉 rs → 
257   (t2 = midtape STape (〈grid,false〉::ls1) 〈c1,false〉 
258     (news@〈newc,false〉::〈grid,false〉::table@〈grid,false〉::rs1) ∧
259    lift_tape ls1 〈newc,false〉 rs1 = 
260    tape_move STape t1' (Some ? 〈〈newc,false〉,move_of_unialpha mv〉)).
261   
262