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/.
29 module P = PrimitiveTactics
31 module S = ProofEngineStructuralRules
32 module F = FreshNamesGenerator
33 module E = ProofEngineTypes
34 module H = ProofEngineHelpers
37 let induction_tac ~term status =
38 let (proof, goal) = status in
40 let module R = CicReduction in
41 let module P = PrimitiveTactics in
42 let module T = Tacticals in
43 let module S = ProofEngineStructuralRules in
44 let module U = UriManager in
45 let (_,metasenv,_,_) = proof in
46 let _,context,ty = CicUtil.lookup_meta goal metasenv in
47 let termty = CicTypeChecker.type_of_aux' metasenv context term in (* per ora non serve *)
49 T.then_ ~start:(T.repeat_tactic
50 ~tactic:(T.then_ ~start:(VariousTactics.generalize_tac ~term) (* chissa' se cosi' funziona? *)
51 ~continuation:(P.intros))
52 ~continuation:(P.elim_intros_simpl ~term)
57 (* unexported tactics *******************************************************)
59 let get_name context index =
60 try match List.nth context (pred index) with
61 | Some (Cic.Name name, _) -> Some name
63 with Invalid_argument "List.nth" -> None
65 let rec scan_tac ~old_context_length ~index ~tactic =
67 let (proof, goal) = status in
68 let _, metasenv, _, _ = proof in
69 let _, context, _ = CicUtil.lookup_meta goal metasenv in
70 let context_length = List.length context in
72 match get_name context index with
73 | _ when index <= 0 -> (proof, [goal])
74 | None -> aux (pred index)
76 let tac = T.then_ ~start:(tactic ~what)
77 ~continuation:(scan_tac ~old_context_length:context_length ~index ~tactic)
79 try E.apply_tactic tac status
80 with E.Fail _ -> aux (pred index)
81 in aux (index + context_length - old_context_length - 1)
85 let rec check_inductive_types types = function
86 | C.MutInd (uri, typeno, _) -> List.mem (uri, typeno) types
87 | C.Appl (hd :: tl) -> check_inductive_types types hd
90 let elim_clear_tac ~mk_fresh_name_callback ~types ~what =
91 let elim_clear_tac status =
92 let (proof, goal) = status in
93 let _, metasenv, _, _ = proof in
94 let _, context, _ = CicUtil.lookup_meta goal metasenv in
95 let index, ty = H.lookup_type metasenv context what in
96 if check_inductive_types types ty then
97 let tac = T.then_ ~start:(P.elim_intros_tac ~mk_fresh_name_callback (C.Rel index))
98 ~continuation:(S.clear what)
100 E.apply_tactic tac status
101 else raise (E.Fail (lazy "unexported elim_clear: not an eliminable type"))
103 E.mk_tactic elim_clear_tac
105 (* elim type ****************************************************************)
107 let elim_type_tac ?(mk_fresh_name_callback = F.mk_fresh_name ~subst:[]) ?depth
111 P.elim_intros_simpl_tac ?using ?depth ~mk_fresh_name_callback what
113 let elim_type_tac status =
115 T.thens ~start: (P.cut_tac what) ~continuations:[elim (C.Rel 1); T.id_tac]
117 E.apply_tactic tac status
119 E.mk_tactic elim_type_tac
121 (* decompose ****************************************************************)
123 (* robaglia --------------------------------------------------------------- *)
125 (** perform debugging output? *)
127 let debug_print = fun _ -> ()
129 (** debugging print *)
130 let warn s = debug_print (lazy ("DECOMPOSE: " ^ (Lazy.force s)))
132 (* search in term the Inductive Types and return a list of uris as triples like this: (uri,typeno,exp_named_subst) *)
133 let search_inductive_types ty =
134 let rec aux types = function
135 | C.MutInd (uri, typeno, _) when (not (List.mem (uri, typeno) types)) ->
136 (uri, typeno) :: types
137 | C.Appl applist -> List.fold_left aux types applist
141 (* N.B: in un caso tipo (and A forall C:Prop.(or B C)) l'or *non* viene selezionato! *)
143 (* roba seria ------------------------------------------------------------- *)
145 let decompose_tac ?(mk_fresh_name_callback = F.mk_fresh_name ~subst:[])
146 ?(user_types=[]) ~dbd what =
147 let decompose_tac status =
148 let (proof, goal) = status in
149 let _, metasenv,_,_ = proof in
150 let _, context, _ = CicUtil.lookup_meta goal metasenv in
151 let types = List.rev_append user_types (FwdQueries.decomposables dbd) in
152 let tactic = elim_clear_tac ~mk_fresh_name_callback ~types in
153 let old_context_length = List.length context in
154 let tac = T.then_ ~start:(tactic ~what)
155 ~continuation:(scan_tac ~old_context_length ~index:1 ~tactic)
157 E.apply_tactic tac status
159 E.mk_tactic decompose_tac
162 module R = CicReduction
164 let rec elim_clear_tac ~term' ~nr_of_hyp_still_to_elim status =
165 let (proof, goal) = status in
166 warn (lazy ("nr_of_hyp_still_to_elim=" ^ (string_of_int nr_of_hyp_still_to_elim)));
167 if nr_of_hyp_still_to_elim <> 0 then
168 let _,metasenv,_,_ = proof in
169 let _,context,_ = CicUtil.lookup_meta goal metasenv in
170 let old_context_len = List.length context in
172 CicTypeChecker.type_of_aux' metasenv context term'
173 CicUniv.empty_ugraph in
174 warn (lazy ("elim_clear termty= " ^ CicPp.ppterm termty));
176 C.MutInd (uri,typeno,exp_named_subst)
177 | C.Appl((C.MutInd (uri,typeno,exp_named_subst))::_)
178 when (List.mem (uri,typeno,exp_named_subst) urilist) ->
179 warn (lazy ("elim " ^ CicPp.ppterm termty));
180 ProofEngineTypes.apply_tactic
182 ~start:(P.elim_intros_simpl_tac term')
184 (* clear the hyp that has just been eliminated *)
185 ProofEngineTypes.mk_tactic (fun status ->
186 let (proof, goal) = status in
187 let _,metasenv,_,_ = proof in
188 let _,context,_ = CicUtil.lookup_meta goal metasenv in
189 let new_context_len = List.length context in
190 warn (lazy ("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)));
191 let new_nr_of_hyp_still_to_elim = nr_of_hyp_still_to_elim + (new_context_len - old_context_len) - 1 in
193 match List.nth context new_nr_of_hyp_still_to_elim with
195 | Some (Cic.Anonymous,_) -> assert false
196 | Some (Cic.Name name,_) -> name
198 ProofEngineTypes.apply_tactic
201 if (term'==term) (* if it's the first application of elim, there's no need to clear the hyp *)
202 then begin debug_print (lazy ("%%%%%%% no clear")); T.id_tac end
203 else begin debug_print (lazy ("%%%%%%% clear " ^ (string_of_int (new_nr_of_hyp_still_to_elim)))); (S.clear ~hyp:hyp_name) end)
204 ~continuation:(ProofEngineTypes.mk_tactic (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)))
209 let new_nr_of_hyp_still_to_elim = nr_of_hyp_still_to_elim - 1 in
210 warn (lazy ("fail; hyp=" ^ (string_of_int new_nr_of_hyp_still_to_elim)));
211 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
212 else (* no hyp to elim left in this goal *)
213 ProofEngineTypes.apply_tactic T.id_tac status
216 elim_clear_tac ~term':term ~nr_of_hyp_still_to_elim:1 status