(* 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 PEH = ProofEngineHelpers *) module U = CicUniv module TC = CicTypeChecker module PET = ProofEngineTypes module S = CicSubstitution module PT = PrimitiveTactics module T = Tacticals module FNG = FreshNamesGenerator module MI = CicMkImplicit module PESR = ProofEngineStructuralRules let fail_msg0 = "unexported clearbody: invalid argument" let fail_msg1 = "fwd: argument is not premise in the current goal" let fail_msg2 = "fwd: no applicable simplification" let error msg = raise (PET.Fail msg) (* unexported tactics *******************************************************) let clearbody ~index = let rec find_name index = function | Some (Cic.Name name, _) :: _ when index = 1 -> name | _ :: tail when index > 1 -> find_name (pred index) tail | _ -> error fail_msg0 in let clearbody status = let (proof, goal) = status in let _, metasenv, _, _ = proof in let _, context, _ = CicUtil.lookup_meta goal metasenv in PET.apply_tactic (PESR.clearbody ~hyp:(find_name index context)) status in PET.mk_tactic clearbody (* lapply *******************************************************************) let strip_prods metasenv context ?how_many to_what term = let irl = MI.identity_relocation_list_for_metavariable context in let mk_meta metasenv its_type = let index = MI.new_meta metasenv [] in let metasenv = [index, context, its_type] @ metasenv in metasenv, Cic.Meta (index, irl), index in let update_counters = function | None, [] -> None, T.id_tac, [] | None, to_what :: tail -> None, PT.apply_tac ~term:to_what, tail | Some hm, [] -> Some (pred hm), T.id_tac, [] | Some hm, to_what :: tail -> Some (pred hm), PT.apply_tac ~term:to_what, tail in let rec aux metasenv metas conts tw = function | Some hm, _ when hm <= 0 -> metasenv, metas, conts | xhm, Cic.Prod (Cic.Name _, t1, t2) -> let metasenv, meta, index = mk_meta metasenv t1 in aux metasenv (meta :: metas) ((T.id_tac, index) :: conts) tw (xhm, (S.subst meta t2)) | xhm, Cic.Prod (Cic.Anonymous, t1, t2) -> let xhm, tac, tw = update_counters (xhm, tw) in let metasenv, meta, index = mk_meta metasenv t1 in aux metasenv (meta :: metas) ((tac, index) :: conts) tw (xhm, (S.subst meta t2)) | _, t -> metasenv, metas, conts in aux metasenv [] [] to_what (how_many, term) let lapply_tac ?(mk_fresh_name_callback = FreshNamesGenerator.mk_fresh_name ~subst:[]) (* ?(substs = []) *) ?how_many ?(to_what = []) what = let letin_tac term = PT.letin_tac ~mk_fresh_name_callback term in let lapply_tac (proof, goal) = let xuri, metasenv, u, t = proof in let _, context, _ = CicUtil.lookup_meta goal metasenv in let lemma, _ = TC.type_of_aux' metasenv context what U.empty_ugraph in let lemma = FNG.clean_dummy_dependent_types lemma in let metasenv, metas, conts = strip_prods metasenv context ?how_many to_what lemma in let conclusion = Cic.Appl (what :: List.rev metas) in let tac = T.thens ~start:(letin_tac conclusion) ~continuations:[clearbody ~index:1] in let proof = (xuri, metasenv, u, t) in let aux (proof, goals) (tac, goal) = let proof, new_goals = PET.apply_tactic tac (proof, goal) in proof, goals @ new_goals in List.fold_left aux (proof, []) ((tac, goal) :: conts) in PET.mk_tactic lapply_tac (* fwd **********************************************************************) let fwd_simpl_tac ?(mk_fresh_name_callback = FreshNamesGenerator.mk_fresh_name ~subst:[]) ~dbd hyp = let find_type metasenv context = let rec aux p = function | Some (Cic.Name name, Cic.Decl t) :: _ when name = hyp -> p, t | Some (Cic.Name name, Cic.Def (_, Some t)) :: _ when name = hyp -> p, t | Some (Cic.Name name, Cic.Def (u, _)) :: tail when name = hyp -> p, fst (TC.type_of_aux' metasenv tail u U.empty_ugraph) | _ :: tail -> aux (succ p) tail | [] -> error fail_msg1 in aux 1 context in let lapply_tac to_what lemma = lapply_tac ~mk_fresh_name_callback ~how_many:1 ~to_what:[to_what] lemma in let fwd_simpl_tac status = let (proof, goal) = status in let _, metasenv, _, _ = proof in let _, context, ty = CicUtil.lookup_meta goal metasenv in let index, major = find_type metasenv context in match MetadataQuery.fwd_simpl ~dbd major with | [] -> error fail_msg2 | uri :: _ -> Printf.eprintf "fwd: %s\n" (UriManager.string_of_uri uri); flush stderr; let start = lapply_tac (Cic.Rel index) (Cic.Const (uri, [])) in let tac = T.thens ~start ~continuations:[PESR.clearbody hyp] in PET.apply_tactic tac status in PET.mk_tactic fwd_simpl_tac