(* 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/. *) open ProofEngineTypes let clearbody ~hyp = let clearbody ~hyp (proof, goal) = let module C = Cic in let curi,metasenv,pbo,pty = proof in let metano,_,_ = CicUtil.lookup_meta goal metasenv in let string_of_name = function C.Name n -> n | C.Anonymous -> "_" in let metasenv' = List.map (function (m,canonical_context,ty) when m = metano -> let canonical_context' = List.fold_right (fun entry context -> match entry with Some (C.Name hyp',C.Def (term,ty)) when hyp = hyp' -> let cleared_entry = let ty = match ty with Some ty -> ty | None -> fst (CicTypeChecker.type_of_aux' metasenv context term CicUniv.empty_ugraph) (* TASSI: FIXME *) in Some (C.Name hyp, Cic.Decl ty) in cleared_entry::context | None -> None::context | Some (n,C.Decl t) | Some (n,C.Def (t,None)) -> let _,_ = try CicTypeChecker.type_of_aux' metasenv context t CicUniv.empty_ugraph (* TASSI: FIXME *) with _ -> raise (Fail ("The correctness of hypothesis " ^ string_of_name n ^ " relies on the body of " ^ hyp) ) in entry::context | Some (_,Cic.Def (_,Some _)) -> assert false ) canonical_context [] in let _,_ = try CicTypeChecker.type_of_aux' metasenv canonical_context' ty CicUniv.empty_ugraph (* TASSI: FIXME *) with _ -> raise (Fail ("The correctness of the goal relies on the body of " ^ hyp)) in m,canonical_context',ty | t -> t ) metasenv in (curi,metasenv',pbo,pty), [goal] in mk_tactic (clearbody ~hyp) let clear ~hyp = let clear ~hyp (proof, goal) = let module C = Cic in let curi,metasenv,pbo,pty = proof in let metano,context,ty = CicUtil.lookup_meta goal metasenv in let string_of_name = function C.Name n -> n | C.Anonymous -> "_" in let metasenv' = List.map (function (m,canonical_context,ty) when m = metano -> let context_changed, canonical_context' = List.fold_right (fun entry (b, context) -> match entry with Some (Cic.Name hyp',_) when hyp' = hyp -> (true, None::context) | None -> (b, None::context) | Some (_,Cic.Def (_,Some _)) -> assert false | Some (n,C.Decl t) | Some (n,C.Def (t,None)) -> if b then let _,_ = try CicTypeChecker.type_of_aux' metasenv context t CicUniv.empty_ugraph with _ -> raise (Fail ("Hypothesis " ^ string_of_name n ^ " uses hypothesis " ^ hyp)) in (b, entry::context) else (b, entry::context) ) canonical_context (false, []) in if not context_changed then raise (Fail ("Hypothesis " ^ hyp ^ " does not exist")); let _,_ = try CicTypeChecker.type_of_aux' metasenv canonical_context' ty CicUniv.empty_ugraph with _ -> raise (Fail ("Hypothesis " ^ hyp ^ " occurs in the goal")) in m,canonical_context',ty | t -> t ) metasenv in (curi,metasenv',pbo,pty), [goal] in mk_tactic (clear ~hyp) let set_goal n = ProofEngineTypes.mk_tactic (fun (proof, goal) -> let (_, metasenv, _, _) = proof in if CicUtil.exists_meta n metasenv then (proof, [n]) else raise (ProofEngineTypes.Fail ("no such meta: " ^ string_of_int n)))