]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/tactics/variousTactics.ml
got rid of ~status label so that tactics can now be applied partially,
[helm.git] / helm / ocaml / tactics / variousTactics.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 let search_theorems_in_context status =
27   let (proof, goal) = status in
28   let module C = Cic in
29   let module R = CicReduction in
30   let module S = CicSubstitution in
31   prerr_endline "Entro in search_context";
32   let _,metasenv,_,_ = proof in
33   let _,context,ty = CicUtil.lookup_meta goal metasenv in
34   let rec find n = function 
35       [] -> []
36     | hd::tl ->
37         let res =
38           try 
39             Some (PrimitiveTactics.apply_tac status ~term:(C.Rel n)) 
40           with 
41             ProofEngineTypes.Fail _ -> None in
42         (match res with
43           Some res -> res::(find (n+1) tl)
44         | None -> find (n+1) tl)
45   in
46   try 
47     let res = find 1 context in
48     prerr_endline "Ho finito context";
49     res 
50   with Failure s -> 
51     prerr_endline ("SIAM QUI = " ^ s); []
52 ;;     
53
54
55 exception NotApplicableTheorem;;
56 exception MaxDepth;;
57
58 let depth = 5;;
59
60 let rec auto_tac mqi_handle level proof goal = 
61 prerr_endline "Entro in Auto_rec";
62 if level = 0 then
63   (* (proof, [goal]) *)
64   (prerr_endline ("NON ci credo");
65    raise MaxDepth)
66 else 
67   (* choices is a list of pairs proof and goallist *)
68   let choices  =
69     (search_theorems_in_context (proof,goal))@ 
70     (TacticChaser.searchTheorems mqi_handle (proof,goal))
71   in
72   let rec try_choices = function
73     [] -> raise NotApplicableTheorem
74   | (proof,goallist)::tl ->
75 prerr_endline ("GOALLIST = " ^ string_of_int (List.length goallist));
76        (try 
77           List.fold_left 
78             (fun proof goal ->
79               (* It may happen that to close the first open goal
80                  also some other goals are closed *)
81               let _,metasenv,_,_ = proof in
82                if List.exists (fun (i,_,_) -> i = goal) metasenv then
83                 let newproof =
84                  auto_tac mqi_handle (level-1) proof goal
85                 in
86                  newproof
87                else
88                 (* goal already closed *)
89                 proof)
90           proof goallist
91         with 
92         | MaxDepth
93         | NotApplicableTheorem ->
94             try_choices tl) in
95  try_choices choices;;
96
97 let auto_tac mqi_handle (proof,goal) =
98   prerr_endline "Entro in Auto";
99   try 
100     let proof = auto_tac mqi_handle depth proof goal in
101 prerr_endline "AUTO_TAC HA FINITO";
102     (proof,[])
103   with 
104   | MaxDepth -> assert false (* this should happens only if depth is 0 above *)
105   | NotApplicableTheorem -> 
106       prerr_endline("No applicable theorem");
107       raise (ProofEngineTypes.Fail "No Applicable theorem");;
108
109 (* TODO se ce n'e' piu' di una, prende la prima che trova... sarebbe meglio
110 chiedere: find dovrebbe restituire una lista di hyp (?) da passare all'utonto con una
111 funzione di callback che restituisce la (sola) hyp da applicare *)
112
113 let assumption_tac status =
114   let (proof, goal) = status in
115   let module C = Cic in
116   let module R = CicReduction in
117   let module S = CicSubstitution in
118    let _,metasenv,_,_ = proof in
119     let _,context,ty = CicUtil.lookup_meta goal metasenv in
120      let rec find n = function 
121         hd::tl -> 
122          (match hd with
123              (Some (_, C.Decl t)) when
124                (R.are_convertible context (S.lift n t) ty) -> n
125            | (Some (_, C.Def (_,Some ty'))) when
126                (R.are_convertible context ty' ty) -> n
127            | (Some (_, C.Def (t,None))) when
128                (R.are_convertible context
129                 (CicTypeChecker.type_of_aux' metasenv context (S.lift n t)) ty) -> n 
130            | _ -> find (n+1) tl
131          )
132       | [] -> raise (ProofEngineTypes.Fail "Assumption: No such assumption")
133      in PrimitiveTactics.apply_tac status ~term:(C.Rel (find 1 context))
134 ;;
135
136 (* ANCORA DA DEBUGGARE *)
137
138 exception AllSelectedTermsMustBeConvertible;;
139
140 (* serve una funzione che cerchi nel ty dal basso a partire da term, i lambda
141 e li aggiunga nel context, poi si conta la lunghezza di questo nuovo
142 contesto e si lifta di tot... COSA SIGNIFICA TUTTO CIO'?????? *)
143
144 let generalize_tac
145  ?(mk_fresh_name_callback = FreshNamesGenerator.mk_fresh_name)
146  terms status
147 =
148   let (proof, goal) = status in
149   let module C = Cic in
150   let module P = PrimitiveTactics in
151   let module T = Tacticals in
152    let _,metasenv,_,_ = proof in
153    let _,context,ty = CicUtil.lookup_meta goal metasenv in
154     let typ =
155      match terms with
156         [] -> assert false
157       | he::tl ->
158          (* We need to check that all the convertibility of all the terms *)
159          List.iter
160           (function t ->
161             if not (CicReduction.are_convertible context he t) then 
162              raise AllSelectedTermsMustBeConvertible
163           ) tl ;
164          (CicTypeChecker.type_of_aux' metasenv context he)
165     in
166      T.thens 
167       ~start:
168         (P.cut_tac 
169          (C.Prod(
170            (mk_fresh_name_callback metasenv context C.Anonymous typ), 
171            typ,
172            (ProofEngineReduction.replace_lifting_csc 1
173              ~equality:(==) 
174              ~what:terms
175              ~with_what:(List.map (function _ -> C.Rel 1) terms)
176              ~where:ty)
177          )))
178       ~continuations: [(P.apply_tac ~term:(C.Rel 1)) ; T.id_tac]
179       status
180 ;;
181
182