X-Git-Url: http://matita.cs.unibo.it/gitweb/?p=helm.git;a=blobdiff_plain;f=helm%2Focaml%2Ftactics%2FeliminationTactics.ml;fp=helm%2Focaml%2Ftactics%2FeliminationTactics.ml;h=e98bcd3c878d6fa597ffda35b85a4ee2e0d4d906;hp=0000000000000000000000000000000000000000;hb=792b5d29ebae8f917043d9dd226692919b5d6ca1;hpb=a14a8c7637fd0b95e9d4deccb20c6abc98e8f953 diff --git a/helm/ocaml/tactics/eliminationTactics.ml b/helm/ocaml/tactics/eliminationTactics.ml new file mode 100644 index 000000000..e98bcd3c8 --- /dev/null +++ b/helm/ocaml/tactics/eliminationTactics.ml @@ -0,0 +1,217 @@ +(* Copyright (C) 2002, HELM Team. + * + * This file is part of HELM, an Hypertextual, Electronic + * Library of Mathematics, developed at the Computer Science + * Department, University of Bologna, Italy. + * + * HELM is free software; you can redistribute it and/or + * modify it under the terms of the GNU General Public License + * as published by the Free Software Foundation; either version 2 + * of the License, or (at your option) any later version. + * + * HELM is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with HELM; if not, write to the Free Software + * Foundation, Inc., 59 Temple Place - Suite 330, Boston, + * MA 02111-1307, USA. + * + * For details, see the HELM World-Wide-Web page, + * http://cs.unibo.it/helm/. + *) + +(* $Id$ *) + +module C = Cic +module P = PrimitiveTactics +module T = Tacticals +module S = ProofEngineStructuralRules +module F = FreshNamesGenerator +module E = ProofEngineTypes +module H = ProofEngineHelpers + +(* +let induction_tac ~term status = + let (proof, goal) = status in + let module C = Cic in + let module R = CicReduction in + let module P = PrimitiveTactics in + let module T = Tacticals in + let module S = ProofEngineStructuralRules in + let module U = UriManager in + let (_,metasenv,_,_) = proof in + let _,context,ty = CicUtil.lookup_meta goal metasenv in + let termty = CicTypeChecker.type_of_aux' metasenv context term in (* per ora non serve *) + + T.then_ ~start:(T.repeat_tactic + ~tactic:(T.then_ ~start:(VariousTactics.generalize_tac ~term) (* chissa' se cosi' funziona? *) + ~continuation:(P.intros)) + ~continuation:(P.elim_intros_simpl ~term) + status +;; +*) + +(* unexported tactics *******************************************************) + +let get_name context index = + try match List.nth context (pred index) with + | Some (Cic.Name name, _) -> Some name + | _ -> None + with Invalid_argument "List.nth" -> None + +let rec scan_tac ~old_context_length ~index ~tactic = + let scan_tac status = + let (proof, goal) = status in + let _, metasenv, _, _ = proof in + let _, context, _ = CicUtil.lookup_meta goal metasenv in + let context_length = List.length context in + let rec aux index = + match get_name context index with + | _ when index <= 0 -> (proof, [goal]) + | None -> aux (pred index) + | Some what -> + let tac = T.then_ ~start:(tactic ~what) + ~continuation:(scan_tac ~old_context_length:context_length ~index ~tactic) + in + try E.apply_tactic tac status + with E.Fail _ -> aux (pred index) + in aux (index + context_length - old_context_length - 1) + in + E.mk_tactic scan_tac + +let rec check_inductive_types types = function + | C.MutInd (uri, typeno, _) -> List.mem (uri, typeno) types + | C.Appl (hd :: tl) -> check_inductive_types types hd + | _ -> false + +let elim_clear_tac ~mk_fresh_name_callback ~types ~what = + let elim_clear_tac status = + let (proof, goal) = status in + let _, metasenv, _, _ = proof in + let _, context, _ = CicUtil.lookup_meta goal metasenv in + let index, ty = H.lookup_type metasenv context what in + if check_inductive_types types ty then + let tac = T.then_ ~start:(P.elim_intros_tac ~mk_fresh_name_callback (C.Rel index)) + ~continuation:(S.clear what) + in + E.apply_tactic tac status + else raise (E.Fail (lazy "unexported elim_clear: not an eliminable type")) + in + E.mk_tactic elim_clear_tac + +(* elim type ****************************************************************) + +let elim_type_tac ?(mk_fresh_name_callback = F.mk_fresh_name ~subst:[]) ?depth + ?using what += + let elim what = + P.elim_intros_simpl_tac ?using ?depth ~mk_fresh_name_callback what + in + let elim_type_tac status = + let tac = + T.thens ~start: (P.cut_tac what) ~continuations:[elim (C.Rel 1); T.id_tac] + in + E.apply_tactic tac status + in + E.mk_tactic elim_type_tac + +(* decompose ****************************************************************) + +(* robaglia --------------------------------------------------------------- *) + + (** perform debugging output? *) +let debug = false +let debug_print = fun _ -> () + + (** debugging print *) +let warn s = debug_print (lazy ("DECOMPOSE: " ^ (Lazy.force s))) + +(* search in term the Inductive Types and return a list of uris as triples like this: (uri,typeno,exp_named_subst) *) +let search_inductive_types ty = + let rec aux types = function + | C.MutInd (uri, typeno, _) when (not (List.mem (uri, typeno) types)) -> + (uri, typeno) :: types + | C.Appl applist -> List.fold_left aux types applist + | _ -> types + in + aux [] ty +(* N.B: in un caso tipo (and A forall C:Prop.(or B C)) l'or *non* viene selezionato! *) + +(* roba seria ------------------------------------------------------------- *) + +let decompose_tac ?(mk_fresh_name_callback = F.mk_fresh_name ~subst:[]) + ?(user_types=[]) ~dbd what = + let decompose_tac status = + let (proof, goal) = status in + let _, metasenv,_,_ = proof in + let _, context, _ = CicUtil.lookup_meta goal metasenv in + let types = List.rev_append user_types (FwdQueries.decomposables dbd) in + let tactic = elim_clear_tac ~mk_fresh_name_callback ~types in + let old_context_length = List.length context in + let tac = T.then_ ~start:(tactic ~what) + ~continuation:(scan_tac ~old_context_length ~index:1 ~tactic) + in + E.apply_tactic tac status + in + E.mk_tactic decompose_tac + +(* +module R = CicReduction + + let rec elim_clear_tac ~term' ~nr_of_hyp_still_to_elim status = + let (proof, goal) = status in + warn (lazy ("nr_of_hyp_still_to_elim=" ^ (string_of_int nr_of_hyp_still_to_elim))); + if nr_of_hyp_still_to_elim <> 0 then + let _,metasenv,_,_ = proof in + let _,context,_ = CicUtil.lookup_meta goal metasenv in + let old_context_len = List.length context in + let termty,_ = + CicTypeChecker.type_of_aux' metasenv context term' + CicUniv.empty_ugraph in + warn (lazy ("elim_clear termty= " ^ CicPp.ppterm termty)); + match termty with + C.MutInd (uri,typeno,exp_named_subst) + | C.Appl((C.MutInd (uri,typeno,exp_named_subst))::_) + when (List.mem (uri,typeno,exp_named_subst) urilist) -> + warn (lazy ("elim " ^ CicPp.ppterm termty)); + ProofEngineTypes.apply_tactic + (T.then_ + ~start:(P.elim_intros_simpl_tac term') + ~continuation:( + (* clear the hyp that has just been eliminated *) + ProofEngineTypes.mk_tactic (fun status -> + let (proof, goal) = status in + let _,metasenv,_,_ = proof in + let _,context,_ = CicUtil.lookup_meta goal metasenv in + let new_context_len = List.length context in + 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))); + let new_nr_of_hyp_still_to_elim = nr_of_hyp_still_to_elim + (new_context_len - old_context_len) - 1 in + let hyp_name = + match List.nth context new_nr_of_hyp_still_to_elim with + None + | Some (Cic.Anonymous,_) -> assert false + | Some (Cic.Name name,_) -> name + in + ProofEngineTypes.apply_tactic + (T.then_ + ~start:( + if (term'==term) (* if it's the first application of elim, there's no need to clear the hyp *) + then begin debug_print (lazy ("%%%%%%% no clear")); T.id_tac end + else begin debug_print (lazy ("%%%%%%% clear " ^ (string_of_int (new_nr_of_hyp_still_to_elim)))); (S.clear ~hyp:hyp_name) end) + ~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))) + status + ))) + status + | _ -> + let new_nr_of_hyp_still_to_elim = nr_of_hyp_still_to_elim - 1 in + warn (lazy ("fail; hyp=" ^ (string_of_int new_nr_of_hyp_still_to_elim))); + 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 + else (* no hyp to elim left in this goal *) + ProofEngineTypes.apply_tactic T.id_tac status + + in + elim_clear_tac ~term':term ~nr_of_hyp_still_to_elim:1 status +*)