(* 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 reduction_tac ~reduction (proof,goal) = let curi,metasenv,pbo,pty = proof in let metano,context,ty = CicUtil.lookup_meta goal metasenv in let new_ty = reduction context ty in let new_metasenv = List.map (function (n,_,_) when n = metano -> (metano,context,new_ty) | _ as t -> t ) metasenv in (curi,new_metasenv,pbo,pty), [metano] ;; *) (* The default of term is the thesis of the goal to be prooved *) let reduction_tac ~reduction ~pattern:(hyp_patterns,goal_pattern) (proof,goal) = let curi,metasenv,pbo,pty = proof in let metano,context,ty = CicUtil.lookup_meta goal metasenv in (* We don't know if [term] is a subterm of [ty] or a subterm of *) (* the type of one metavariable. So we replace it everywhere. *) (*CSC: Il vero problema e' che non sapendo dove sia il term non *) (*CSC: sappiamo neppure quale sia il suo contesto!!!! Insomma, *) (*CSC: e' meglio prima cercare il termine e scoprirne il *) (*CSC: contesto, poi ridurre e infine rimpiazzare. *) let replace context where terms = (*CSC: Per il momento se la riduzione fallisce significa solamente che *) (*CSC: siamo nel contesto errato. Metto il try, ma che schifo!!!! *) (*CSC: Anche perche' cosi' catturo anche quelle del replace che non dovrei *) try let terms' = List.map (reduction context) terms in ProofEngineReduction.replace ~equality:(==) ~what:terms ~with_what:terms' ~where:where with _ -> where in let find_pattern_for name = try Some (snd(List.find (fun (n, pat) -> Cic.Name n = name) hyp_patterns)) with Not_found -> None in let ty' = match goal_pattern with | None -> replace context ty [ty] | Some pat -> let terms = CicUtil.select ~term:ty ~context:pat in let terms = List.map snd terms in replace context ty terms in let context' = if hyp_patterns <> [] then List.fold_right (fun entry context -> match entry with | Some (name,Cic.Decl term) -> (match find_pattern_for name with | None -> entry::context | Some pat -> let terms = CicUtil.select ~term ~context:pat in let terms = List.map snd terms in let where = replace context term terms in let entry = Some (name,Cic.Decl where) in entry::context) | Some (name,Cic.Def (term, None)) -> (match find_pattern_for name with | None -> entry::context | Some pat -> let terms = CicUtil.select ~term ~context:pat in let terms = List.map snd terms in let where = replace context term terms in let entry = Some (name,Cic.Def (where,None)) in entry::context) | _ -> entry::context ) context [] else context in let metasenv' = List.map (function | (n,_,_) when n = metano -> (metano,context',ty') | _ as t -> t ) metasenv in (curi,metasenv',pbo,pty), [metano] ;; let simpl_tac ~pattern = mk_tactic (reduction_tac ~reduction:ProofEngineReduction.simpl ~pattern);; let reduce_tac ~pattern = mk_tactic (reduction_tac ~reduction:ProofEngineReduction.reduce ~pattern);; let whd_tac ~pattern = mk_tactic (reduction_tac ~reduction:CicReduction.whd ~pattern);; let normalize_tac ~pattern = mk_tactic (reduction_tac ~reduction:CicReduction.normalize ~pattern );; let fold_tac ~reduction ~also_in_hypotheses ~term = let fold_tac ~reduction ~also_in_hypotheses ~term (proof,goal) = let curi,metasenv,pbo,pty = proof in let metano,context,ty = CicUtil.lookup_meta goal metasenv in let term' = reduction context term in (* We don't know if [term] is a subterm of [ty] or a subterm of *) (* the type of one metavariable. So we replace it everywhere. *) (*CSC: ma si potrebbe ovviare al problema. Ma non credo *) (*CSC: che si guadagni nulla in fatto di efficienza. *) let replace = ProofEngineReduction.replace ~equality:(=) ~what:[term'] ~with_what:[term] in let ty' = replace ty in let metasenv' = let context' = if also_in_hypotheses then List.map (function Some (n,Cic.Decl t) -> Some (n,Cic.Decl (replace t)) | Some (n,Cic.Def (t,None)) -> Some (n,Cic.Def ((replace t),None)) | None -> None | Some (_,Cic.Def (_,Some _)) -> assert false ) context else context in List.map (function (n,_,_) when n = metano -> (metano,context',ty') | _ as t -> t ) metasenv in (curi,metasenv',pbo,pty), [metano] in mk_tactic (fold_tac ~reduction ~also_in_hypotheses ~term) ;;