]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/tactics/filter_auto.ml
debian version 0.0.6-6
[helm.git] / helm / ocaml / tactics / filter_auto.ml
1 (* Copyright (C) 2000-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
27 let in_hypothesis = "'http://www.cs.unibo.it/helm/schemas/schema-helm#InHypothesis'" ;;
28
29 let main_hypothesis = "'http://www.cs.unibo.it/helm/schemas/schema-helm#MainHypothesis'" ;;
30
31 let main_conclusion = "'http://www.cs.unibo.it/helm/schemas/schema-helm#MainConclusion'" ;;
32
33 let in_conclusion = "'http://www.cs.unibo.it/helm/schemas/schema-helm#InConclusion'" ;;
34
35 let in_body = "'http://www.cs.unibo.it/helm/schemas/schema-helm#InBody'";;
36
37 let escape = Str.global_replace (Str.regexp_string "\'") "\\'";;
38
39 let hyp_const (conn:Mysql.dbd) uri =
40   let uri = escape uri in
41   (*query to obtain all the constants in the hypothesis and conclusion of the theorem*)
42   let query =
43      "select h_occurrence from refObj where source='"^uri^
44     "' and (not (h_position ="^in_body^"))" in
45   (*prerr_endline ("$$$$$$$$$$$$$$$"^query);*)
46   let result = Mysql.exec conn query in 
47   (* now we transform the result in a set *)
48   let f a = 
49     match (Array.to_list a) with
50         [Some uri] -> uri
51       | _ -> assert false in
52   let result = Mysql.map ~f:f result in
53   List.fold_left 
54     (fun set uri ->
55        NewConstraints.StringSet.add uri set)
56     NewConstraints.StringSet.empty result
57 ;;
58
59 (* for each uri check if its costants are a subset of
60    const, the set of the costants of the proof *)
61 let filter_new_constants (conn:Mysql.dbd) const (_,uri) =
62    let hyp = hyp_const conn uri in
63  (*  prerr_endline (NewConstraints.pp_StringSet hyp);*)
64     NewConstraints.StringSet.subset hyp const
65 ;;
66
67
68
69
70 let rec exec_query (conn:Mysql.dbd) (uris,main) k  = 
71   let add_must (n,from,where) uri =
72     let refObjn = "refObj" ^ (string_of_int n) in
73     let new_must =
74       [ refObjn^".h_occurrence = '" ^ uri ^ "'";
75         "(not ("^refObjn^".h_position ="^in_body^"))"] in
76     let where' = 
77       if n = 0 then new_must@where
78       else 
79        (refObjn^".source = refObj" ^ (string_of_int (n-1)) 
80        ^ ".source")::new_must@where in
81   (n+1,("refObj as "^refObjn)::from,where')
82   in
83   let (_,from,where) = 
84     List.fold_left add_must (0,[],[]) uris in
85   let from,where = 
86     ["no_concl_hyp";"refObj as main"]@from, 
87     ["no=" ^ (string_of_int k);
88      "no_concl_hyp.source = refObj0.source";
89      "main.source = refObj0.source";
90      "main.h_occurrence = '" ^ main ^ "'";
91      "main.h_position = " ^ main_conclusion]@where
92   in
93   let from = String.concat "," from in
94   let where = String.concat " and " where in
95   let query = "select distinct(refObj0.source) from " ^ from ^ " where " ^ where in
96      (*prerr_endline query;*)
97     Mysql.exec conn query
98 ;;
99
100 let powerset set =
101   let rec powerset_r set sub =
102     if (NewConstraints.StringSet.is_empty set) then sub
103     else 
104       let a = NewConstraints.StringSet.min_elt set in
105       let newset = NewConstraints.StringSet.remove a set in
106       let newsub = NewConstraints.SetSet.union (NewConstraints.SetSet.add (NewConstraints.StringSet.singleton a)
107                    (NewConstraints.SetSet.fold 
108                        (fun s t -> (NewConstraints.SetSet.add (NewConstraints.StringSet.add a s) t)) 
109                             sub NewConstraints.SetSet.empty)) sub in
110       powerset_r newset newsub in
111 powerset_r set NewConstraints.SetSet.empty
112 ;;
113
114 let setset_to_listlist setset =
115   let listset = NewConstraints.SetSet.elements setset in
116   let res = 
117     List.map 
118       (fun set -> 
119          let el = NewConstraints.StringSet.elements set in
120          (List.length el, el)) listset in
121     (* ordered by descending cardinality *)
122 List.sort (fun (n,_) (m,_) -> m - n) res
123
124 let exist_element list_of_uris (_,uri) =
125   let ex u =
126     if u = uri then true
127     else false
128   in
129 List.exists ex list_of_uris
130 ;;
131     
132
133 let filter_uris (conn:Mysql.dbd) const uris main =
134   let subsets_of_consts = 
135     setset_to_listlist (powerset const) in
136   let ex u =
137     if u = main then true
138     else false
139   in
140   let subsets_of_consts =
141   List.filter 
142         (fun (_,b) -> (List.exists ex b)) 
143                 subsets_of_consts in
144   let uris_of_const =
145     List.concat
146      (List.map 
147               (fun (m,s) -> 
148                  (let res = 
149                     exec_query conn (s,main) m in
150                   let f a = 
151                     match (Array.to_list a) with
152                         [Some uri] -> uri
153                         | _ -> assert false in
154                     Mysql.map ~f:f res))
155               subsets_of_consts)
156       in
157 List.filter (exist_element uris_of_const) uris
158 ;;  
159    
160 let rec power n m =
161   if (m = 1) then n
162   else n*(power n (m-1))
163 ;;
164         
165