1 (* Copyright (C) 2002, HELM Team.
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.
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.
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.
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,
22 * For details, see the HELM World-Wide-Web page,
23 * http://cs.unibo.it/helm/.
28 (** perform debugging output? *)
31 (** debugging print *)
34 prerr_endline ("DECOMPOSE: " ^ s)
39 let induction_tac ~term ~status:((proof,goal) as status) =
41 let module R = CicReduction in
42 let module P = PrimitiveTactics in
43 let module T = Tacticals in
44 let module S = ProofEngineStructuralRules in
45 let module U = UriManager in
46 let (_,metasenv,_,_) = proof in
47 let _,context,ty = List.find (function (m,_,_) -> m=goal) metasenv in
48 let termty = CicTypeChecker.type_of_aux' metasenv context term in (* per ora non serve *)
50 T.then_ ~start:(T.repeat_tactic
51 ~tactic:(T.then_ ~start:(VariousTactics.generalize_tac ~term) (* chissa' se cosi' funziona? *)
52 ~continuation:(P.intros))
53 ~continuation:(P.elim_intros_simpl ~term)
59 let elim_type_tac ~term ~status =
61 let module P = PrimitiveTactics in
62 let module T = Tacticals in
64 ~start: (P.cut_tac term)
65 ~continuations:[ P.elim_intros_simpl_tac ~term:(C.Rel 1) ; T.id_tac ]
70 (* Decompose related stuff *)
72 exception InteractiveUserUriChoiceNotRegistered
74 let interactive_user_uri_choice =
75 (ref (fun ~selection_mode -> raise InteractiveUserUriChoiceNotRegistered) :
76 (selection_mode:[`SINGLE | `EXTENDED] ->
78 ?enable_button_for_non_vars:bool ->
79 title:string -> msg:string -> string list -> string list) ref)
82 exception IllFormedUri of string
84 let cic_textual_parser_uri_of_string uri' =
87 if String.sub uri' (String.length uri' - 4) 4 = ".con" then
88 CicTextualParser0.ConUri (UriManager.uri_of_string uri')
90 if String.sub uri' (String.length uri' - 4) 4 = ".var" then
91 CicTextualParser0.VarUri (UriManager.uri_of_string uri')
95 let uri'',typeno = CicTextualLexer.indtyuri_of_uri uri' in
96 CicTextualParser0.IndTyUri (uri'',typeno)
99 (* Constructor of an Inductive Type *)
100 let uri'',typeno,consno =
101 CicTextualLexer.indconuri_of_uri uri'
103 CicTextualParser0.IndConUri (uri'',typeno,consno)
106 _ -> raise (IllFormedUri uri')
110 let constructor_uri_of_string uri =
111 match cic_textual_parser_uri_of_string uri with
112 CicTextualParser0.IndTyUri (uri,typeno) -> (uri,typeno,[])
117 (* N.B.: nella finestra c'e' un campo "nessuno deei precedenti, prova questo" che non ha senso? *)
118 (* N.B.: in questo passaggio perdo l'informazione su exp_named_subst !!!! *)
119 (* domanda: due triple possono essere diverse solo per avere exp_named_subst diverse?? *)
120 let module U = UriManager in
122 (constructor_uri_of_string)
123 (!interactive_user_uri_choice
124 ~selection_mode:`EXTENDED ~ok:"Ok" ~enable_button_for_non_vars:false
125 ~title:"Decompose" ~msg:"Please, select the Inductive Types to decompose"
127 (function (uri,typeno,_) -> U.string_of_uri uri ^ "#1/" ^ string_of_int (typeno+1))
133 let decompose_tac ?(uris_choice_callback=(function l -> l)) term ~status:((proof,goal) as status) =
134 let module C = Cic in
135 let module R = CicReduction in
136 let module P = PrimitiveTactics in
137 let module T = Tacticals in
138 let module S = ProofEngineStructuralRules in
139 let _,metasenv,_,_ = proof in
140 let _,context,ty = List.find (function (m,_,_) -> m=goal) metasenv in
141 let old_context_len = List.length context in
142 let termty = CicTypeChecker.type_of_aux' metasenv context term in
144 let rec make_list termty =
145 (* N.B.: altamente inefficente? *)
146 let rec search_inductive_types urilist termty =
147 (* search in term the Inductive Types and return a list of uris as triples like this: (uri,typeno,exp_named_subst) *)
149 (C.MutInd (uri,typeno,exp_named_subst)) (* when (not (List.mem (uri,typeno,exp_named_subst) urilist)) *) ->
150 (uri,typeno,exp_named_subst)::urilist
151 | (C.Appl ((C.MutInd (uri,typeno,exp_named_subst))::applist)) (* when (not (List.mem (uri,typeno,exp_named_subst) urilist)) *) ->
152 (uri,typeno,exp_named_subst)::(List.fold_left search_inductive_types urilist applist)
154 (* N.B: in un caso tipo (and A !C:Prop.(or B C)) l'or *non* viene selezionato! *)
156 let rec purge_duplicates urilist =
157 let rec aux triple urilist =
163 else hd::(aux triple tl)
167 | hd::tl -> hd::(purge_duplicates (aux hd tl))
169 purge_duplicates (search_inductive_types [] termty)
173 (* list of triples (uri,typeno,exp_named_subst) of Inductive Types found in term and chosen by the user *)
174 (* N.B.: due to a bug in uris_choice_callback exp_named_subst are not significant (they all are []) *)
175 uris_choice_callback (make_list termty) in
177 let rec elim_clear_tac ~term' ~nr_of_hyp_still_to_elim ~status:((proof,goal) as status) =
178 warn ("nr_of_hyp_still_to_elim=" ^ (string_of_int nr_of_hyp_still_to_elim));
179 if nr_of_hyp_still_to_elim <> 0 then
180 let _,metasenv,_,_ = proof in
181 let _,context,_ = List.find (function (m,_,_) -> m=goal) metasenv in
182 let old_context_len = List.length context in
183 let termty = CicTypeChecker.type_of_aux' metasenv context term' in
184 warn ("elim_clear termty= " ^ CicPp.ppterm termty);
186 C.MutInd (uri,typeno,exp_named_subst)
187 | C.Appl((C.MutInd (uri,typeno,exp_named_subst))::_)
188 when (List.mem (uri,typeno,exp_named_subst) urilist) ->
189 warn ("elim " ^ CicPp.ppterm termty);
191 ~start:(P.elim_intros_simpl_tac ~term:term')
193 (* clear the hyp that has just been eliminated *)
194 (fun ~status:((proof,goal) as status) ->
195 let _,metasenv,_,_ = proof in
196 let _,context,_ = List.find (function (m,_,_) -> m=goal) metasenv in
197 let new_context_len = List.length context in
198 warn ("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));
199 let new_nr_of_hyp_still_to_elim = nr_of_hyp_still_to_elim + (new_context_len - old_context_len) - 1 in
202 if (term'==term) (* if it's the first application of elim, there's no need to clear the hyp *)
203 then begin prerr_endline ("%%%%%%% no clear"); T.id_tac end
204 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)
205 ~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)
210 let new_nr_of_hyp_still_to_elim = nr_of_hyp_still_to_elim - 1 in
211 warn ("fail; hyp=" ^ (string_of_int new_nr_of_hyp_still_to_elim));
212 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
213 else (* no hyp to elim left in this goal *)
217 elim_clear_tac ~term':term ~nr_of_hyp_still_to_elim:1 ~status