]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/tactics/variousTactics.ml
bb5be64d8837a8592560ecaf7ef8a3f6072672e1
[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 exception NotAProposition;;
55 exception NotApplicableTheorem;;
56 exception MaxDepth;;
57
58 let depth = 3;;
59
60 let rec auto_tac_aux mqi_handle level proof goal = 
61 prerr_endline ("Entro in Auto_rec; level = " ^ (string_of_int level));
62 if level = 0 then
63   (* (proof, [goal]) *)
64   (prerr_endline ("MaxDepth");
65    raise MaxDepth)
66 else 
67   (* let us verify that the metavariable is still an open goal --
68      it could have been closed by closing other goals -- and that
69      it is of sort Prop *)
70   let _,metasenv,_,_ = proof in
71   let meta_inf = 
72     (try 
73        let (_, ey ,ty) = CicUtil.lookup_meta goal metasenv in
74          Some (ey, ty)
75      with _ -> None) in
76   match meta_inf with
77       Some (ey, ty) ->
78         prerr_endline ("CURRENT GOAL = " ^ (CicPp.ppterm ty));
79         (*
80         let time1 = Unix.gettimeofday() in
81         let _, all_paths = NewConstraints.prefixes 5 ty in
82         let time2 = Unix.gettimeofday() in
83         prerr_endline 
84           (Printf.sprintf "TEMPO DI CALCOLO = %1.3f" (time2 -. time1) );
85         prerr_endline 
86           ("ALL PATHS: n = " ^ string_of_int 
87              (List.length all_paths));
88         prerr_endline (NewConstraints.pp_prefixes all_paths); 
89         *)
90         (* if the goal does not have a sort Prop we return the
91            current proof and a list containing the goal *)
92         let ty_sort = CicTypeChecker.type_of_aux' metasenv ey ty in
93           if CicReduction.are_convertible 
94             ey (Cic.Sort Cic.Prop) ty_sort then
95             (* sort Prop *)
96             (* choices is a list of pairs proof and goallist *)
97             let choices  =
98               (search_theorems_in_context (proof,goal))@ 
99               (TacticChaser.searchTheorems mqi_handle (proof,goal)) 
100             in
101             let rec try_choices = function
102                 [] -> raise NotApplicableTheorem
103               | (proof,goallist)::tl ->
104 prerr_endline ("GOALLIST = " ^ string_of_int (List.length goallist));
105                   (try 
106                      List.fold_left 
107                        (fun proof goal ->
108                             auto_tac_aux mqi_handle (level-1) proof goal)
109                        proof goallist
110                    with 
111                      | MaxDepth
112                      | NotApplicableTheorem 
113                      | NotAProposition ->
114                          try_choices tl) in
115               try_choices choices
116           else
117             (* CUT AND PASTE DI PROVA !! *)
118             let choices  =
119               (search_theorems_in_context (proof,goal))@ 
120               (TacticChaser.searchTheorems mqi_handle (proof,goal)) 
121             in
122             let rec try_choices = function
123                 [] -> raise NotApplicableTheorem
124               | (proof,[])::tl -> proof
125               | _::tl -> try_choices tl in
126             try_choices choices
127             (* raise NotAProposition *)
128     | None -> proof
129 ;;
130
131 let auto_tac mqi_handle (proof,goal) =
132   prerr_endline "Entro in Auto";
133   try 
134     let proof = auto_tac_aux mqi_handle depth proof goal in
135 prerr_endline "AUTO_TAC HA FINITO";
136     (proof,[])
137   with 
138   | MaxDepth -> assert false (* this should happens only if depth is 0 above *)
139   | NotApplicableTheorem -> 
140       prerr_endline("No applicable theorem");
141       raise (ProofEngineTypes.Fail "No Applicable theorem");;
142
143 (* TODO se ce n'e' piu' di una, prende la prima che trova... sarebbe meglio
144 chiedere: find dovrebbe restituire una lista di hyp (?) da passare all'utonto con una
145 funzione di callback che restituisce la (sola) hyp da applicare *)
146
147 let assumption_tac status =
148   let (proof, goal) = status in
149   let module C = Cic in
150   let module R = CicReduction in
151   let module S = CicSubstitution in
152    let _,metasenv,_,_ = proof in
153     let _,context,ty = CicUtil.lookup_meta goal metasenv in
154      let rec find n = function 
155         hd::tl -> 
156          (match hd with
157              (Some (_, C.Decl t)) when
158                (R.are_convertible context (S.lift n t) ty) -> n
159            | (Some (_, C.Def (_,Some ty'))) when
160                (R.are_convertible context ty' ty) -> n
161            | (Some (_, C.Def (t,None))) when
162                (R.are_convertible context
163                 (CicTypeChecker.type_of_aux' metasenv context (S.lift n t)) ty) -> n 
164            | _ -> find (n+1) tl
165          )
166       | [] -> raise (ProofEngineTypes.Fail "Assumption: No such assumption")
167      in PrimitiveTactics.apply_tac status ~term:(C.Rel (find 1 context))
168 ;;
169
170 (* ANCORA DA DEBUGGARE *)
171
172 exception AllSelectedTermsMustBeConvertible;;
173
174 (* serve una funzione che cerchi nel ty dal basso a partire da term, i lambda
175 e li aggiunga nel context, poi si conta la lunghezza di questo nuovo
176 contesto e si lifta di tot... COSA SIGNIFICA TUTTO CIO'?????? *)
177
178 let generalize_tac
179  ?(mk_fresh_name_callback = FreshNamesGenerator.mk_fresh_name)
180  terms status
181 =
182   let (proof, goal) = status in
183   let module C = Cic in
184   let module P = PrimitiveTactics in
185   let module T = Tacticals in
186    let _,metasenv,_,_ = proof in
187    let _,context,ty = CicUtil.lookup_meta goal metasenv in
188     let typ =
189      match terms with
190         [] -> assert false
191       | he::tl ->
192          (* We need to check that all the convertibility of all the terms *)
193          List.iter
194           (function t ->
195             if not (CicReduction.are_convertible context he t) then 
196              raise AllSelectedTermsMustBeConvertible
197           ) tl ;
198          (CicTypeChecker.type_of_aux' metasenv context he)
199     in
200      T.thens 
201       ~start:
202         (P.cut_tac 
203          (C.Prod(
204            (mk_fresh_name_callback metasenv context C.Anonymous typ), 
205            typ,
206            (ProofEngineReduction.replace_lifting_csc 1
207              ~equality:(==) 
208              ~what:terms
209              ~with_what:(List.map (function _ -> C.Rel 1) terms)
210              ~where:ty)
211          )))
212       ~continuations: [(P.apply_tac ~term:(C.Rel 1)) ; T.id_tac]
213       status
214 ;;
215
216