]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/metadata/metadataDb.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / metadata / metadataDb.ml
1 (* Copyright (C) 2004, 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://helm.cs.unibo.it/
24  *)
25
26 open MetadataTypes
27
28 open Printf
29
30 let execute_insert dbd uri (sort_cols, rel_cols, obj_cols) =
31   let sort_tuples = 
32     List.fold_left (fun s l -> match l with
33       | [`String a; `String b; `Int c; `String d] -> 
34           sprintf "(\"%s\", \"%s\", %d, \"%s\")" a b c d :: s
35       | _ -> assert false )
36     [] sort_cols
37   in
38   let rel_tuples =
39     List.fold_left (fun s l -> match l with
40       | [`String a; `String b; `Int c] ->
41           sprintf "(\"%s\", \"%s\", %d)" a b c :: s
42       | _ -> assert false)
43     [] rel_cols  
44   in
45   let obj_tuples = List.fold_left (fun s l -> match l with
46       | [`String a; `String b; `String c; `Int d] ->
47           sprintf "(\"%s\", \"%s\", \"%s\", %d)" a b c d :: s
48       | [`String a; `String b; `String c; `Null] ->
49           sprintf "(\"%s\", \"%s\", \"%s\", %s)" a b c "NULL" :: s
50       | _ -> assert false)
51     [] obj_cols
52   in
53   if sort_tuples <> [] then
54     begin
55     let query_sort = 
56       sprintf "INSERT %s VALUES %s;" (sort_tbl ()) (String.concat "," sort_tuples) 
57     in
58     ignore (HMysql.exec dbd query_sort)
59     end;
60   if rel_tuples <> [] then
61     begin
62     let query_rel = 
63       sprintf "INSERT %s VALUES %s;" (rel_tbl ()) (String.concat "," rel_tuples) 
64     in
65     ignore (HMysql.exec dbd query_rel)
66     end;
67   if obj_tuples <> [] then
68     begin
69     let query_obj = 
70       sprintf "INSERT %s VALUES %s;" (obj_tbl ()) (String.concat "," obj_tuples) 
71     in
72     ignore (HMysql.exec dbd query_obj)
73     end
74   
75     
76 let count_distinct position l =
77   MetadataConstraints.UriManagerSet.cardinal
78   (List.fold_left (fun acc d -> 
79     match position with
80     | `Conclusion -> 
81          (match d with
82          | `Obj (name,`InConclusion) 
83          | `Obj (name,`MainConclusion _ ) -> 
84              MetadataConstraints.UriManagerSet.add name acc
85          | _ -> acc)
86     | `Hypothesis ->
87         (match d with
88         | `Obj (name,`InHypothesis) 
89         | `Obj (name,`MainHypothesis _) -> 
90             MetadataConstraints.UriManagerSet.add name acc
91         | _ -> acc)
92     | `Statement ->
93         (match d with
94         | `Obj (name,`InBody) -> acc
95         | `Obj (name,_) -> MetadataConstraints.UriManagerSet.add name acc
96         | _ -> acc)
97     ) MetadataConstraints.UriManagerSet.empty l)
98
99 let insert_const_no ~dbd l =
100  let data =
101   List.fold_left
102    (fun acc (uri,_,metadata) -> 
103      let no_concl = count_distinct `Conclusion metadata in
104      let no_hyp = count_distinct `Hypothesis metadata in
105      let no_full = count_distinct `Statement metadata in
106       (sprintf "(\"%s\", %d, %d, %d)" 
107        (UriManager.string_of_uri uri) no_concl no_hyp no_full) :: acc
108    ) [] l in
109  let insert =
110   sprintf "INSERT INTO %s VALUES %s" (count_tbl ()) (String.concat "," data)
111  in
112   ignore (HMysql.exec dbd insert)
113   
114 let insert_name ~dbd l =
115  let data =
116   List.fold_left
117    (fun acc (uri,name,_) -> 
118       (sprintf "(\"%s\", \"%s\")" (UriManager.string_of_uri uri) name) :: acc
119    ) [] l in
120  let insert =
121   sprintf "INSERT INTO %s VALUES %s" (name_tbl ()) (String.concat "," data)
122  in
123   ignore (HMysql.exec dbd insert)
124
125 type columns =
126   MetadataPp.t list list * MetadataPp.t list list * MetadataPp.t list list
127
128   (* TODO ZACK: verify if an object has already been indexed *)
129 let already_indexed _ = false
130
131 (***** TENTATIVE HACK FOR THE DB SLOWDOWN - BEGIN *******)
132 let analyze_index = ref 0
133 let eventually_analyze dbd =
134   incr analyze_index;
135   if !analyze_index > 30 then
136     begin
137       let analyze t = "OPTIMIZE TABLE " ^ t ^ ";" in
138       List.iter 
139         (fun table -> ignore (HMysql.exec dbd (analyze table)))
140         [name_tbl (); rel_tbl (); sort_tbl (); obj_tbl(); count_tbl()]
141     end
142   
143 (***** TENTATIVE HACK FOR THE DB SLOWDOWN - END *******)
144
145 let index_obj ~dbd ~uri = 
146   if not (already_indexed uri) then begin
147     eventually_analyze dbd;
148     let metadata = MetadataExtractor.compute_obj uri in
149     let uri = UriManager.string_of_uri uri in
150     let columns = MetadataPp.columns_of_metadata metadata in
151     execute_insert dbd uri (columns :> columns);
152     insert_const_no ~dbd metadata;
153     insert_name ~dbd metadata
154   end
155   
156
157 let tables_to_clean =
158   [sort_tbl; rel_tbl; obj_tbl; name_tbl; count_tbl]
159
160 let clean ~(dbd:HMysql.dbd) =
161   let owned_uris =  (* list of uris in list-of-columns format *)
162     let query = sprintf "SELECT source FROM %s" (name_tbl ()) in
163     let result = HMysql.exec dbd query in
164     let uris = HMysql.map result (fun cols ->
165       match cols.(0) with
166       | Some src -> src
167       | None -> assert false) in
168     (* and now some stuff to remove #xpointers and duplicates *)
169     uris
170   in
171   let del_from tbl =
172     let query s = 
173       sprintf "DELETE FROM %s WHERE source LIKE \"%s%%\"" (tbl ()) s 
174     in
175     List.iter
176       (fun source_col -> ignore (HMysql.exec dbd (query source_col)))
177       owned_uris
178   in
179   List.iter del_from tables_to_clean;
180   owned_uris
181
182 let unindex ~dbd ~uri =
183   let uri = UriManager.string_of_uri uri in
184   let del_from tbl =
185     let query tbl =
186       sprintf "DELETE FROM %s WHERE source LIKE \"%s%%\"" (tbl ()) uri
187     in
188     ignore (HMysql.exec dbd (query tbl))
189   in
190   List.iter del_from tables_to_clean
191