]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/metadata/metadataDb.ml
added "unindex" to undo indexing of a single object
[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 prepare_insert () =
31   (*
32   let insert_owner a b =
33     sprintf "INSERT %s VALUES (\"%s\", \"%s\")" (owners_tbl ())a b
34   in
35   *)
36   let insert_sort  a b c d =
37     sprintf "INSERT %s VALUES (\"%s\", \"%s\", %d, \"%s\")" (sort_tbl ())a b c d
38   in
39   let insert_rel a b c =
40     sprintf "INSERT %s VALUES (\"%s\", \"%s\", %d)" (rel_tbl ()) a b c
41   in
42   let insert_obj a b c d =
43     sprintf "INSERT %s VALUES (\"%s\", \"%s\", \"%s\", %s)" (obj_tbl ()) a b c d
44   in
45   ((*insert_owner, *)insert_sort, insert_rel, insert_obj)
46
47 let execute_insert dbd ((*insert_owner, *)insert_sort, insert_rel, insert_obj)
48   uri (sort_cols, rel_cols, obj_cols)
49 =
50   (* ignore (Mysql.exec dbd (insert_owner uri owner)); *)
51   List.iter (function
52       | [`String a; `String b; `Int c; `String d] ->
53           ignore (Mysql.exec dbd (insert_sort a b c d))
54       | _ -> assert false)
55     sort_cols;
56   List.iter (function
57       | [`String a; `String b; `Int c] ->
58           ignore (Mysql.exec dbd (insert_rel a b c))
59       | _ -> assert false)
60     rel_cols;
61   List.iter (function
62       | [`String a; `String b; `String c; `Int d] ->
63           ignore (Mysql.exec dbd (insert_obj a b c (string_of_int d)))
64       | [`String a; `String b; `String c; `Null] ->
65           ignore (Mysql.exec dbd (insert_obj a b c "NULL"))
66       | _ -> assert false)
67     obj_cols
68
69 let insert_const_no dbd uri =
70   let inconcl_no =
71     sprintf "INSERT %s SELECT \"%s\", COUNT(DISTINCT h_occurrence) FROM %s WHERE (h_position=\"%s\" OR h_position=\"%s\") AND source LIKE \"%s%%\""
72       (conclno_tbl ()) uri (obj_tbl ()) inconcl_pos mainconcl_pos uri
73   in
74   let concl_hyp =
75     sprintf "INSERT %s
76         SELECT \"%s\",COUNT(DISTINCT h_occurrence)
77         FROM %s
78         WHERE NOT (h_position=\"%s\") AND (source = \"%s\")"
79       (conclno_hyp_tbl ()) uri (obj_tbl ()) inbody_pos uri
80   in
81   ignore (Mysql.exec dbd inconcl_no);
82   ignore (Mysql.exec dbd concl_hyp)
83
84 let insert_name ~dbd ~uri ~name =
85   let query =
86     sprintf "INSERT %s VALUES (\"%s\", \"%s\")" (name_tbl ()) uri name
87   in
88   ignore (Mysql.exec dbd query)
89
90 type columns =
91   MetadataPp.t list list * MetadataPp.t list list * MetadataPp.t list list
92
93   (* TODO ZACK: verify if an object has already been indexed *)
94 let already_indexed _ = false
95
96 let index_constant ~dbd =
97   let query = prepare_insert () in
98   fun ~uri ~body ~ty  ->
99     if not (already_indexed uri) then begin
100       let name = UriManager.name_of_uri uri in
101       let uri = UriManager.string_of_uri uri in
102       let metadata = MetadataExtractor.compute ~body ~ty in
103       let columns = MetadataPp.columns_of_metadata ~about:uri metadata in
104       execute_insert dbd query uri (columns :> columns);
105       insert_const_no dbd uri;
106       insert_name ~dbd ~uri ~name
107     end
108
109 let index_inductive_def ~dbd =
110   let query = prepare_insert () in
111   fun ~uri ~types ->
112     if not (already_indexed uri) then begin
113       let metadata = MetadataExtractor.compute_ind ~uri ~types in
114       let uri_of (a,b,c) = a in
115       let uris = UriManager.string_of_uri uri :: List.map uri_of metadata in
116       let uri = UriManager.string_of_uri uri in
117       let columns = MetadataPp.columns_of_ind_metadata metadata in
118       execute_insert dbd query uri (columns :> columns);
119       List.iter (insert_const_no dbd) uris;
120       List.iter (fun (uri, name, _) -> insert_name ~dbd ~uri ~name) metadata
121     end
122
123 let tables_to_clean =
124   [sort_tbl; rel_tbl; obj_tbl; conclno_tbl; conclno_hyp_tbl; name_tbl]
125
126 let clean ~(dbd:Mysql.dbd) =
127   let owned_uris =  (* list of uris in list-of-columns format *)
128     let query = sprintf "SELECT source FROM %s" (obj_tbl ()) in
129     let result = Mysql.exec dbd query in
130     let uris = Mysql.map result (fun cols ->
131       match cols.(0) with
132       | Some src -> src
133       | None -> assert false) in
134     (* and now some stuff to remove #xpointers and duplicates *)
135     uris
136   in
137   let del_from tbl =
138     let query s = 
139       sprintf "DELETE FROM %s WHERE source LIKE \"%s%%\"" (tbl ()) s 
140     in
141     List.iter
142       (fun source_col -> ignore (Mysql.exec dbd (query source_col)))
143       owned_uris
144   in
145   List.iter del_from tables_to_clean;
146   owned_uris
147
148 let unindex ~dbd ~uri =
149   let uri = UriManager.string_of_uri uri in
150   let del_from tbl =
151     let query tbl =
152       sprintf "DELETE FROM %s WHERE source LIKE \"%s%%\"" (tbl ()) uri
153     in
154     ignore (Mysql.exec dbd (query tbl))
155   in
156   List.iter del_from tables_to_clean
157