(* 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/. *) module MI = CicMkImplicit module TC = CicTypeChecker module PET = ProofEngineTypes module U = CicUniv module S = CicSubstitution module PT = PrimitiveTactics (* let module R = CicReduction *) let fail_msg0 = "not a declaration of the current context" let fail_msg1 = "no applicable simplification" let error msg = raise (PET.Fail msg) let rec declaration name = function | [] -> error fail_msg0 | Some (hyp, Cic.Decl ty) :: _ when hyp = name -> ty | _ :: tail -> declaration name tail (* lapply *******************************************************************) let lapply_tac ?(mk_fresh_name_callback = FreshNamesGenerator.mk_fresh_name ~subst:[]) ?(substs = []) what = let rec strip_dependent_prods metasenv context ss = function | Cic.Prod (name, t1, t2) as t -> if TC.does_not_occur context 0 1 t2 then metasenv, ss, t else let metasenv, index = MI.mk_implicit metasenv [] context in let rs = MI.identity_relocation_list_for_metavariable context in let e, s = Some (name, Cic.Decl t1), Some (Cic.Meta (index, rs)) in strip_dependent_prods metasenv (e :: context) (s :: ss) t2 | t -> metasenv, ss, t in let update_metasenv metasenv ((xuri, _, u,t), goal) = ((xuri, metasenv, u,t), goal) in let lapply_tac status = let (proof, goal) = status in let _,metasenv,_,_ = proof in let _,context,ty = CicUtil.lookup_meta goal metasenv in let lemma, _ = TC.type_of_aux' metasenv context what U.empty_ugraph in let metasenv, substs, stripped_lemma = strip_dependent_prods metasenv context [] lemma in let status = update_metasenv metasenv status in let holed_lemma = S.subst_meta substs stripped_lemma in PET.apply_tactic (PT.cut_tac ~mk_fresh_name_callback holed_lemma) status in PET.mk_tactic lapply_tac (* fwd **********************************************************************) let fwd_simpl_tac ~hyp ~dbd = let fwd_simpl_tac status = let (proof, goal) = status in let _,metasenv,_,_ = proof in let _,context,ty = CicUtil.lookup_meta goal metasenv in let major = declaration hyp context in match MetadataQuery.fwd_simpl ~dbd major with | [] -> error fail_msg1 | uri :: _ -> prerr_endline (UriManager.string_of_uri uri); (proof, []) in PET.mk_tactic fwd_simpl_tac