]> matita.cs.unibo.it Git - helm.git/blob - components/tactics/declarative.ml
50d4be88435e650976eda3fd9052f697bd87e0f1
[helm.git] / components / tactics / declarative.ml
1 (* Copyright (C) 2006, 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 assume id t =
27   Tacticals.then_
28      ~start:
29        (Tactics.intros ~howmany:1
30         ~mk_fresh_name_callback:(fun _ _ _ ~typ -> Cic.Name id) ())
31      ~continuation:
32        (Tactics.change ~pattern:(None,[id,Cic.Implicit (Some `Hole)],None)
33          (fun _ metasenv ugraph -> t,metasenv,ugraph))
34 ;;
35
36 let suppose t id ty =
37 (*BUG: ty not used *)
38  Tacticals.then_
39    ~start:
40        (Tactics.intros ~howmany:1
41              ~mk_fresh_name_callback:(fun _ _ _ ~typ -> Cic.Name id) ())
42    ~continuation:
43             (Tactics.change ~pattern:(None,[id,Cic.Implicit (Some `Hole)],None)  
44               (fun _ metasenv ugraph -> t,metasenv,ugraph))
45 ;;
46
47 let by_term_we_proved t ty id ty' =
48 (*BUG: ty' not used *)
49  match t with
50     None -> assert false
51   | Some t ->
52      Tacticals.thens
53      ~start:
54        (Tactics.cut ty
55          ~mk_fresh_name_callback:(fun _ _ _  ~typ -> Cic.Name id))
56      ~continuations:
57        [ Tacticals.id_tac ; Tactics.apply t ]
58 ;;
59
60 let bydone t =
61    match t with
62     None -> assert false
63   | Some t ->
64     (Tactics.apply ~term:t)
65 ;;
66
67 let we_need_to_prove t id ty =
68 (*BUG: ty not used *)
69  let aux status =
70   let proof,goals =
71    ProofEngineTypes.apply_tactic
72     (Tactics.cut t
73       ~mk_fresh_name_callback:(fun _ _ _  ~typ -> Cic.Name id))
74     status
75   in
76    let goals' =
77     match goals with
78        [fst; snd] -> [snd; fst]
79      | _ -> assert false
80    in
81     proof,goals'
82  in
83   ProofEngineTypes.mk_tactic aux
84 ;;
85
86 let existselim t id1 t1 id2 t2 =
87 (*BUG: t1 and t2 not used *)
88 (*PARSING BUG: t2 is parsed in the current context, but it may
89   have occurrences of id1 in it *)
90  Tactics.elim_intros t
91   ~mk_fresh_name_callback:
92     (let i = ref 0 in
93       fun _ _ _  ~typ ->
94        incr i;
95        if !i = 1 then Cic.Name id1 else Cic.Name id2)
96
97 let andelim = existselim;;
98
99 let rewritingstep lhs rhs just conclude =
100  let aux ((proof,goal) as status) =
101   let (curi,metasenv,proofbo,proofty) = proof in
102   let _,context,_ = CicUtil.lookup_meta goal metasenv in
103   let eq,trans =
104    match LibraryObjects.eq_URI () with
105       None -> assert false (*TODO*)
106     | Some uri ->
107       Cic.MutInd (uri,0,[]), Cic.Const (LibraryObjects.trans_eq_URI ~eq:uri,[])
108   in
109   let ty,_ =
110    CicTypeChecker.type_of_aux' metasenv context rhs CicUniv.empty_ugraph in
111   let just =
112    match just with
113       None -> assert false (*TOOD*)
114     | Some just -> just
115   in
116    match lhs with
117       None ->
118        let plhs,prhs =
119         match 
120          fst
121           (CicTypeChecker.type_of_aux' metasenv context (Cic.Rel 1)
122             CicUniv.empty_ugraph)
123         with
124            Cic.Appl [_;_;plhs;prhs] -> plhs,prhs
125          | _ -> assert false in
126        let last_hyp_name =
127         match context with
128            (Some (Cic.Name id,_))::_ -> id
129          | _ -> assert false
130        in
131         (match conclude with
132             None ->
133              ProofEngineTypes.apply_tactic
134               (Tacticals.thens
135                 ~start:(Tactics.apply ~term:trans)
136                 ~continuations:
137                   [ Tactics.apply prhs ;
138                     Tactics.apply (Cic.Rel 1) ;
139                     Tactics.apply just]) status
140           | Some name ->
141              let mk_fresh_name_callback =
142               fun metasenv context _ ~typ ->
143                 FreshNamesGenerator.mk_fresh_name ~subst:[]
144                  metasenv context name ~typ
145              in
146               ProofEngineTypes.apply_tactic
147                (Tacticals.thens
148                  ~start:(Tactics.cut ~mk_fresh_name_callback
149                   (Cic.Appl [eq ; ty ; plhs ; rhs]))
150                  ~continuations:
151                    [ Tactics.clear ~hyps:[last_hyp_name] ;
152                      Tacticals.thens
153                       ~start:(Tactics.apply ~term:trans)
154                       ~continuations:
155                         [ Tactics.apply prhs ;
156                           Tactics.apply (Cic.Rel 1) ;
157                           Tactics.apply just]
158                    ]) status)
159     | Some lhs ->
160        match conclude with
161           None -> ProofEngineTypes.apply_tactic (Tactics.apply just) status
162         | Some name ->
163             let mk_fresh_name_callback =
164              fun metasenv context _ ~typ ->
165                FreshNamesGenerator.mk_fresh_name ~subst:[]
166                 metasenv context name ~typ
167             in
168              ProofEngineTypes.apply_tactic
169               (Tacticals.thens
170                 ~start:
171                   (Tactics.cut ~mk_fresh_name_callback
172                     (Cic.Appl [eq ; ty ; lhs ; rhs]))
173                 ~continuations:[ Tacticals.id_tac ; Tactics.apply just ]) status
174  in
175   ProofEngineTypes.mk_tactic aux
176 ;;
177
178 let we_proceed_by_induction_on t pat =
179  (*BUG here: pat unused *)
180  Tactics.elim_intros ~depth:0 t
181 ;;
182
183 let case id ~params =
184  (*BUG here: id unused*)
185  (*BUG here: it does not verify that the previous branch is closed *)
186  (*BUG here: the params should be parsed telescopically*)
187  (*BUG here: the tactic_terms should be terms*)
188  let rec aux ~params ((proof,goal) as status) =
189   match params with
190      [] -> proof,[goal]
191    | (id,t)::tl ->
192       match ProofEngineTypes.apply_tactic (assume id t) status with
193          proof,[goal] -> aux tl (proof,goal)
194        | _ -> assert false
195  in
196   ProofEngineTypes.mk_tactic (aux ~params)
197 ;;
198
199 let thesisbecomes t =
200  (*BUG here: nothing done*)
201  Tacticals.id_tac
202 ;;
203
204 let byinduction t id  = suppose t id None;;