]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/tactics/eliminationTactics.ml
73d1771ff6d0002c0ece8743c09d25fcfac72dc0
[helm.git] / helm / ocaml / tactics / eliminationTactics.ml
1 (* Copyright (C) 2002, HELM Team.
2  *
3  * This file is part of HELM, an Hypertextual, Electronic
4  * Library of Mathematics, developed at the Computer Science
5  * Department, University of Bologna, Italy.
6  *
7  * HELM is free software; you can redistribute it and/or
8  * modify it under the terms of the GNU General Public License
9  * as published by the Free Software Foundation; either version 2
10  * of the License, or (at your option) any later version.
11  *
12  * HELM is distributed in the hope that it will be useful,
13  * but WITHOUT ANY WARRANTY; without even the implied warranty of
14  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15  * GNU General Public License for more details.
16  *
17  * You should have received a copy of the GNU General Public License
18  * along with HELM; if not, write to the Free Software
19  * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
20  * MA  02111-1307, USA.
21  *
22  * For details, see the HELM World-Wide-Web page,
23  * http://cs.unibo.it/helm/.
24  *)
25
26 (*
27 let induction_tac ~term ~status:((proof,goal) as status) =
28   let module C = Cic in
29   let module R = CicReduction in
30   let module P = PrimitiveTactics in
31   let module T = Tacticals in
32   let module S = ProofEngineStructuralRules in
33   let module U = UriManager in 
34    let (_,metasenv,_,_) = proof in
35     let _,context,ty = List.find (function (m,_,_) -> m=goal) metasenv in
36      let termty = CicTypeChecker.type_of_aux' metasenv context term in  (* per ora non serve *)
37
38      T.then_ ~start:(T.repeat_tactic 
39                        ~tactic:(T.then_ ~start:(VariousTactics.generalize_tac ~term) (* chissa' se cosi' funziona? *)
40                        ~continuation:(P.intros))
41              ~continuation:(P.elim_intros_simpl ~term)
42              ~status
43 ;;
44 *)
45
46
47 let elim_type_tac ~term ~status =
48   let module C = Cic in
49   let module P = PrimitiveTactics in
50   let module T = Tacticals in
51    T.thens
52     ~start: (P.cut_tac term)
53     ~continuations:[ P.elim_intros_simpl_tac ~term:(C.Rel 1) ; T.id_tac ]
54     ~status
55 ;;
56
57 (* Questa era gia' in ring.ml!!!! NB: adesso in ring non c'e' piu' :-)
58 let elim_type_tac ~term ~status =
59   warn "in Ring.elim_type_tac";
60   Tacticals.thens ~start:(cut_tac ~term)
61    ~continuations:[elim_simpl_intros_tac ~term:(Cic.Rel 1) ; Tacticals.id_tac] ~status
62 *)
63
64
65 (* PROVE DI DECOMPOSE *)
66 (* guardare quali sono i tipi induttivi decomponibili presenti in
67 profondita' nel term; chiamare una funzione di call-back passando questa
68 lista e ritornando la lista di termini che l'utente vuole decomporre;
69 decomporre. *)
70
71
72 exception IllFormedUri of string
73
74 let cic_textual_parser_uri_of_string uri' =
75  try
76   (* Constant *)
77   if String.sub uri' (String.length uri' - 4) 4 = ".con" then
78    CicTextualParser0.ConUri (UriManager.uri_of_string uri')
79   else
80    if String.sub uri' (String.length uri' - 4) 4 = ".var" then
81     CicTextualParser0.VarUri (UriManager.uri_of_string uri')
82    else
83     (try
84       (* Inductive Type *)
85       let uri'',typeno = CicTextualLexer.indtyuri_of_uri uri' in
86        CicTextualParser0.IndTyUri (uri'',typeno)
87      with
88       _ ->
89        (* Constructor of an Inductive Type *)
90        let uri'',typeno,consno =
91         CicTextualLexer.indconuri_of_uri uri'
92        in
93         CicTextualParser0.IndConUri (uri'',typeno,consno)
94     )
95  with
96   _ -> raise (IllFormedUri uri')
97 ;;
98
99 let decompose_tac ?(uris_choice_callback=(function l -> l)) term
100  ~status:((proof,goal) as status)
101 =
102   let module C = Cic in
103   let module R = CicReduction in
104   let module P = PrimitiveTactics in
105   let module T = Tacticals in
106   let module S = ProofEngineStructuralRules in
107    let _,metasenv,_,_ = proof in
108     let _,context,ty = List.find (function (m,_,_) -> m=goal) metasenv in
109      let old_context_len = List.length context in
110 (*     let nr_of_hyp_still_to_elim = ref 1 in *)
111      let termty = CicTypeChecker.type_of_aux' metasenv context term in
112
113       let rec make_list termty = 
114 (* altamente inefficente? *)
115        let rec search_inductive_types urilist termty =
116         (* search in term the Inductive Types and return a list of uris as triples like this: (uri,typeno,exp_named_subst) *)
117         match termty with
118            (C.MutInd (uri,typeno,exp_named_subst)) (* when (not (List.mem (uri,typeno,exp_named_subst) urilist)) *) -> 
119                (uri,typeno,exp_named_subst)::urilist
120          | (C.Appl ((C.MutInd (uri,typeno,exp_named_subst))::applist)) (* when (not (List.mem (uri,typeno,exp_named_subst) urilist)) *) -> 
121                (uri,typeno,exp_named_subst)::(List.fold_left search_inductive_types urilist applist)
122          | _ -> urilist
123          (* N.B: in un caso tipo (and A !C:Prop.(or B C)) l'or *non* viene selezionato! *)
124        in 
125        let rec purge_duplicates urilist = 
126         let rec aux triple urilist =
127          match urilist with 
128             [] -> []
129           | hd::tl -> 
130              if (hd = triple) 
131               then aux triple tl
132               else hd::(aux triple tl)
133         in
134         match urilist with
135            [] -> []
136          | hd::tl -> hd::(purge_duplicates (aux hd tl))
137        in
138         purge_duplicates (search_inductive_types [] termty) 
139       in
140
141        let urilist =  
142           (* list of triples (uri,typeno,exp_named_subst) of Inductive Types found in term and chosen by the user *)
143           (* N.B.: due to a bug in uris_choice_callback exp_named_subst are not significant (they all are []) *)
144          uris_choice_callback (make_list termty) in
145
146         let rec elim_clear_tac ~term' ~nr_of_hyp_still_to_elim ~status:((proof,goal) as status) =
147 prerr_endline ("%%%%%%% nr_of_hyp_still_to_elim=" ^ (string_of_int nr_of_hyp_still_to_elim));
148          if nr_of_hyp_still_to_elim <> 0 then
149           let _,metasenv,_,_ = proof in
150            let _,context,_ = List.find (function (m,_,_) -> m=goal) metasenv in
151             let old_context_len = List.length context in
152             let termty = CicTypeChecker.type_of_aux' metasenv context term' in
153 prerr_endline ("%%%%%%% elim_clear termty= " ^ CicPp.ppterm termty);
154              match termty with
155                 C.MutInd (uri,typeno,exp_named_subst)
156               | C.Appl((C.MutInd (uri,typeno,exp_named_subst))::_) 
157                  when (List.mem (uri,typeno,exp_named_subst) urilist) ->
158 prerr_endline ("%%%%%%% elim " ^ CicPp.ppterm termty);
159                    T.then_ 
160                       ~start:(P.elim_intros_simpl_tac ~term:term')
161                       ~continuation:(
162                         (* clear the hyp that has just been eliminated *)
163                         (fun ~status:((proof,goal) as status) -> 
164                           let _,metasenv,_,_ = proof in
165                            let _,context,_ = List.find (function (m,_,_) -> m=goal) metasenv in
166                             let new_context_len = List.length context in   
167 prerr_endline ("%%%%%%% newcon=" ^ (string_of_int new_context_len) ^ " & oldcon=" ^ (string_of_int old_context_len) ^ " & old_nr_of_hyp=" ^ (string_of_int nr_of_hyp_still_to_elim));
168                              let new_nr_of_hyp_still_to_elim = nr_of_hyp_still_to_elim + (new_context_len - old_context_len) - 1 in
169                              T.then_ 
170                                 ~start:(
171                                   if (term'==term) (* this is the first application of elim: there's no need to clear the hyp *) 
172                                    then begin prerr_endline ("%%%%%%% no clear"); T.id_tac end
173                                    else begin prerr_endline ("%%%%%%% clear " ^ (string_of_int (new_nr_of_hyp_still_to_elim))); (S.clear ~hyp:(List.nth context (new_nr_of_hyp_still_to_elim))) end)
174                                 ~continuation:(elim_clear_tac ~term':(C.Rel new_nr_of_hyp_still_to_elim) ~nr_of_hyp_still_to_elim:new_nr_of_hyp_still_to_elim)
175                                 ~status
176                         ))
177                       ~status
178               | _ ->
179                    let new_nr_of_hyp_still_to_elim = nr_of_hyp_still_to_elim - 1 in 
180 prerr_endline ("%%%%%%% fail; hyp=" ^ (string_of_int new_nr_of_hyp_still_to_elim));
181                     elim_clear_tac ~term':(C.Rel new_nr_of_hyp_still_to_elim) ~nr_of_hyp_still_to_elim:new_nr_of_hyp_still_to_elim ~status
182          else (* raise (ProofEngineTypes.Fail "Decomopse: finished decomposing"); *) T.id_tac ~status
183
184         in
185 (*         T.repeat_tactic ~tactic: *)
186               (elim_clear_tac ~term':term ~nr_of_hyp_still_to_elim:1)
187             ~status
188 ;;
189
190
191