]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/tactics/reductionTactics.ml
new implementation (due to paths).
[helm.git] / helm / ocaml / tactics / reductionTactics.ml
1 (* Copyright (C) 2002, HELM Team.
2  * 
3  * This file is part of HELM, an Hypertextual, Electronic
4  * Library of Mathematics, developed at the Computer Science
5  * Department, University of Bologna, Italy.
6  * 
7  * HELM is free software; you can redistribute it and/or
8  * modify it under the terms of the GNU General Public License
9  * as published by the Free Software Foundation; either version 2
10  * of the License, or (at your option) any later version.
11  * 
12  * HELM is distributed in the hope that it will be useful,
13  * but WITHOUT ANY WARRANTY; without even the implied warranty of
14  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15  * GNU General Public License for more details.
16  *
17  * You should have received a copy of the GNU General Public License
18  * along with HELM; if not, write to the Free Software
19  * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
20  * MA  02111-1307, USA.
21  * 
22  * For details, see the HELM World-Wide-Web page,
23  * http://cs.unibo.it/helm/.
24  *)
25
26 open ProofEngineTypes
27
28 (*
29 let reduction_tac ~reduction (proof,goal) =
30  let curi,metasenv,pbo,pty = proof in
31  let metano,context,ty = CicUtil.lookup_meta goal metasenv in
32   let new_ty = reduction context ty in
33    let new_metasenv = 
34     List.map
35     (function
36       (n,_,_) when n = metano -> (metano,context,new_ty)
37       | _ as t -> t
38     ) metasenv
39    in
40     (curi,new_metasenv,pbo,pty), [metano]
41 ;;
42 *)
43
44 (* The default of term is the thesis of the goal to be prooved *)
45 let reduction_tac ~reduction ~pattern:(hyp_patterns,goal_pattern) (proof,goal) =
46   let curi,metasenv,pbo,pty = proof in
47   let metano,context,ty = CicUtil.lookup_meta goal metasenv in
48   (* We don't know if [term] is a subterm of [ty] or a subterm of *)
49   (* the type of one metavariable. So we replace it everywhere.   *)
50   (*CSC: Il vero problema e' che non sapendo dove sia il term non *)
51   (*CSC: sappiamo neppure quale sia il suo contesto!!!! Insomma,  *)
52   (*CSC: e' meglio prima cercare il termine e scoprirne il        *)
53   (*CSC: contesto, poi ridurre e infine rimpiazzare.              *)
54   let replace context where terms =
55   (*CSC: Per il momento se la riduzione fallisce significa solamente che     *)
56   (*CSC: siamo nel contesto errato. Metto il try, ma che schifo!!!!          *)
57   (*CSC: Anche perche' cosi' catturo anche quelle del replace che non dovrei *)
58     try
59      let terms, terms' = 
60        List.split
61        (List.map 
62        (fun i, t -> t, 
63           (let x, _, _ = CicMetaSubst.delift_rels [] metasenv i t in
64           let t' = reduction context x in 
65           CicSubstitution.lift i t'))
66        terms)
67      in
68       ProofEngineReduction.replace ~equality:(==) ~what:terms ~with_what:terms'
69        ~where:where
70     (* FIXME this is a catch ALL... bad thing *)
71     with exc -> (*prerr_endline (Printexc.to_string exc);*) where
72   in
73   let find_pattern_for name =
74     try Some (snd(List.find (fun (n, pat) -> Cic.Name n = name) hyp_patterns))
75     with Not_found -> None
76   in
77   let ty' = 
78     match goal_pattern with
79     | None -> replace context ty [0,ty]
80     | Some pat -> 
81         let terms = CicUtil.select ~term:ty ~context:pat in
82         replace context ty terms
83   in
84   let context' =
85     if hyp_patterns <> [] then
86     List.fold_right
87      (fun entry context ->
88        match entry with
89        | Some (name,Cic.Decl term) ->
90            (match find_pattern_for name with
91            | None -> entry::context
92            | Some pat -> 
93                let terms = CicUtil.select ~term ~context:pat in
94                let where = replace context term terms in
95                let entry = Some (name,Cic.Decl where) in
96                entry::context)
97        | Some (name,Cic.Def (term, None)) ->
98            (match find_pattern_for name with
99            | None -> entry::context
100            | Some pat -> 
101                let terms = CicUtil.select ~term ~context:pat in
102                let where = replace context term terms in
103                let entry = Some (name,Cic.Def (where,None)) in
104                entry::context)
105        | _ -> entry::context
106      ) context []
107    else
108     context
109   in
110   let metasenv' = 
111     List.map (function 
112       | (n,_,_) when n = metano -> (metano,context',ty')
113       | _ as t -> t
114     ) metasenv
115   in
116   (curi,metasenv',pbo,pty), [metano]
117 ;;
118
119 let simpl_tac ~pattern = 
120  mk_tactic (reduction_tac ~reduction:ProofEngineReduction.simpl ~pattern);;
121
122 let reduce_tac ~pattern = 
123  mk_tactic (reduction_tac ~reduction:ProofEngineReduction.reduce ~pattern);;
124   
125 let whd_tac ~pattern = 
126  mk_tactic (reduction_tac ~reduction:CicReduction.whd ~pattern);;
127
128 let normalize_tac ~pattern = 
129  mk_tactic (reduction_tac ~reduction:CicReduction.normalize ~pattern );;
130
131 let fold_tac ~reduction ~also_in_hypotheses ~term =
132  let fold_tac ~reduction ~also_in_hypotheses ~term (proof,goal) =
133   let curi,metasenv,pbo,pty = proof in
134   let metano,context,ty = CicUtil.lookup_meta goal metasenv in
135    let term' = reduction context term in
136     (* We don't know if [term] is a subterm of [ty] or a subterm of *)
137     (* the type of one metavariable. So we replace it everywhere.   *)
138     (*CSC: ma si potrebbe ovviare al problema. Ma non credo *)
139     (*CSC: che si guadagni nulla in fatto di efficienza.    *) 
140     let replace =
141      ProofEngineReduction.replace ~equality:(=) ~what:[term'] ~with_what:[term]
142     in
143      let ty' = replace ty in
144      let metasenv' =
145       let context' =
146        if also_in_hypotheses then
147         List.map
148          (function
149              Some (n,Cic.Decl t) -> Some (n,Cic.Decl (replace t))
150            | Some (n,Cic.Def (t,None))  -> Some (n,Cic.Def ((replace t),None))
151            | None -> None
152            | Some (_,Cic.Def (_,Some _)) -> assert false
153          ) context
154        else
155         context
156       in
157        List.map
158         (function
159             (n,_,_) when n = metano -> (metano,context',ty')
160           | _ as t -> t
161         ) metasenv
162       
163      in
164       (curi,metasenv',pbo,pty), [metano]
165  in
166   mk_tactic (fold_tac ~reduction ~also_in_hypotheses ~term)
167 ;;