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