]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/metadata/metadataDb.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / metadata / metadataDb.ml
index a4e6008a8a0ff22e6ebe526e4845d490657bee5b..c5fbb79a832ac642a3584d93a270fd931140c94b 100644 (file)
@@ -55,98 +55,113 @@ let execute_insert dbd uri (sort_cols, rel_cols, obj_cols) =
     let query_sort = 
       sprintf "INSERT %s VALUES %s;" (sort_tbl ()) (String.concat "," sort_tuples) 
     in
-    ignore (Mysql.exec dbd query_sort)
+    ignore (HMysql.exec dbd query_sort)
     end;
   if rel_tuples <> [] then
     begin
     let query_rel = 
       sprintf "INSERT %s VALUES %s;" (rel_tbl ()) (String.concat "," rel_tuples) 
     in
-    ignore (Mysql.exec dbd query_rel)
+    ignore (HMysql.exec dbd query_rel)
     end;
   if obj_tuples <> [] then
     begin
     let query_obj = 
       sprintf "INSERT %s VALUES %s;" (obj_tbl ()) (String.concat "," obj_tuples) 
     in
-    ignore (Mysql.exec dbd query_obj)
+    ignore (HMysql.exec dbd query_obj)
     end
   
-let insert_const_no dbd uri =
-  let inconcl_no =
-    sprintf "INSERT %s SELECT \"%s\", COUNT(DISTINCT h_occurrence) FROM %s WHERE (h_position=\"%s\" OR h_position=\"%s\") AND source LIKE \"%s%%\""
-      (conclno_tbl ()) uri (obj_tbl ()) inconcl_pos mainconcl_pos uri
-  in
-  let concl_hyp =
-    sprintf "INSERT %s
-        SELECT \"%s\",COUNT(DISTINCT h_occurrence)
-        FROM %s
-        WHERE NOT (h_position=\"%s\") AND (source = \"%s\")"
-      (fullno_tbl ()) uri (obj_tbl ()) inbody_pos uri
-  in
-  ignore (Mysql.exec dbd inconcl_no);
-  ignore (Mysql.exec dbd concl_hyp)
+    
+let count_distinct position l =
+  MetadataConstraints.UriManagerSet.cardinal
+  (List.fold_left (fun acc d -> 
+    match position with
+    | `Conclusion -> 
+         (match d with
+         | `Obj (name,`InConclusion) 
+         | `Obj (name,`MainConclusion _ ) -> 
+             MetadataConstraints.UriManagerSet.add name acc
+         | _ -> acc)
+    | `Hypothesis ->
+        (match d with
+        | `Obj (name,`InHypothesis) 
+        | `Obj (name,`MainHypothesis _) -> 
+            MetadataConstraints.UriManagerSet.add name acc
+        | _ -> acc)
+    | `Statement ->
+        (match d with
+        | `Obj (name,`InBody) -> acc
+        | `Obj (name,_) -> MetadataConstraints.UriManagerSet.add name acc
+        | _ -> acc)
+    ) MetadataConstraints.UriManagerSet.empty l)
 
-let insert_name ~dbd ~uri ~name =
-  let query =
-    sprintf "INSERT %s VALUES (\"%s\", \"%s\")" (name_tbl ()) uri name
-  in
-  ignore (Mysql.exec dbd query)
+let insert_const_no ~dbd l =
+ let data =
+  List.fold_left
+   (fun acc (uri,_,metadata) -> 
+     let no_concl = count_distinct `Conclusion metadata in
+     let no_hyp = count_distinct `Hypothesis metadata in
+     let no_full = count_distinct `Statement metadata in
+      (sprintf "(\"%s\", %d, %d, %d)" 
+       (UriManager.string_of_uri uri) no_concl no_hyp no_full) :: acc
+   ) [] l in
+ let insert =
+  sprintf "INSERT INTO %s VALUES %s" (count_tbl ()) (String.concat "," data)
+ in
+  ignore (HMysql.exec dbd insert)
+  
+let insert_name ~dbd l =
+ let data =
+  List.fold_left
+   (fun acc (uri,name,_) -> 
+      (sprintf "(\"%s\", \"%s\")" (UriManager.string_of_uri uri) name) :: acc
+   ) [] l in
+ let insert =
+  sprintf "INSERT INTO %s VALUES %s" (name_tbl ()) (String.concat "," data)
+ in
+  ignore (HMysql.exec dbd insert)
 
 type columns =
   MetadataPp.t list list * MetadataPp.t list list * MetadataPp.t list list
 
   (* TODO ZACK: verify if an object has already been indexed *)
 let already_indexed _ = false
-(*
-let index_constant ~dbd =
-  let query = prepare_insert () in
-  fun ~uri ~body ~ty  ->
-    if not (already_indexed uri) then begin
-      let name = UriManager.name_of_uri uri in
-      let uri = UriManager.string_of_uri uri in
-      let metadata = MetadataExtractor.compute ~body ~ty in
-      let columns = MetadataPp.columns_of_metadata ~about:uri metadata in
-      execute_insert dbd query uri (columns :> columns);
-      insert_const_no dbd uri;
-      insert_name ~dbd ~uri ~name
-    end
 
-let index_inductive_def ~dbd =
-  let query = prepare_insert () in
-  fun ~uri ~types ->
-    if not (already_indexed uri) then begin
-      let metadata = MetadataExtractor.compute_obj uri in
-      let uri_of (a,b,c) = a in
-      let uris = UriManager.string_of_uri uri :: List.map uri_of metadata in
-      let uri = UriManager.string_of_uri uri in
-      let columns = MetadataPp.columns_of_ind_metadata metadata in
-      execute_insert dbd query uri (columns :> columns);
-      List.iter (insert_const_no dbd) uris;
-      List.iter (fun (uri, name, _) -> insert_name ~dbd ~uri ~name) metadata
+(***** TENTATIVE HACK FOR THE DB SLOWDOWN - BEGIN *******)
+let analyze_index = ref 0
+let eventually_analyze dbd =
+  incr analyze_index;
+  if !analyze_index > 30 then
+    begin
+      let analyze t = "OPTIMIZE TABLE " ^ t ^ ";" in
+      List.iter 
+        (fun table -> ignore (HMysql.exec dbd (analyze table)))
+        [name_tbl (); rel_tbl (); sort_tbl (); obj_tbl(); count_tbl()]
     end
-*)
+  
+(***** TENTATIVE HACK FOR THE DB SLOWDOWN - END *******)
+
 let index_obj ~dbd ~uri = 
   if not (already_indexed uri) then begin
+    eventually_analyze dbd;
     let metadata = MetadataExtractor.compute_obj uri in
-    let uri_of (a,b,c) = a in
-    let uris = UriManager.string_of_uri uri :: List.map uri_of metadata in
     let uri = UriManager.string_of_uri uri in
     let columns = MetadataPp.columns_of_metadata metadata in
     execute_insert dbd uri (columns :> columns);
-    List.iter (insert_const_no dbd) uris;
-    List.iter (fun (uri, name, _) -> insert_name ~dbd ~uri ~name) metadata
+    insert_const_no ~dbd metadata;
+    insert_name ~dbd metadata
   end
   
 
 let tables_to_clean =
-  [sort_tbl; rel_tbl; obj_tbl; conclno_tbl; fullno_tbl; name_tbl; hypno_tbl]
+  [sort_tbl; rel_tbl; obj_tbl; name_tbl; count_tbl]
 
-let clean ~(dbd:Mysql.dbd) =
+let clean ~(dbd:HMysql.dbd) =
   let owned_uris =  (* list of uris in list-of-columns format *)
-    let query = sprintf "SELECT source FROM %s" (obj_tbl ()) in
-    let result = Mysql.exec dbd query in
-    let uris = Mysql.map result (fun cols ->
+    let query = sprintf "SELECT source FROM %s" (name_tbl ()) in
+    let result = HMysql.exec dbd query in
+    let uris = HMysql.map result (fun cols ->
       match cols.(0) with
       | Some src -> src
       | None -> assert false) in
@@ -158,7 +173,7 @@ let clean ~(dbd:Mysql.dbd) =
       sprintf "DELETE FROM %s WHERE source LIKE \"%s%%\"" (tbl ()) s 
     in
     List.iter
-      (fun source_col -> ignore (Mysql.exec dbd (query source_col)))
+      (fun source_col -> ignore (HMysql.exec dbd (query source_col)))
       owned_uris
   in
   List.iter del_from tables_to_clean;
@@ -170,7 +185,7 @@ let unindex ~dbd ~uri =
     let query tbl =
       sprintf "DELETE FROM %s WHERE source LIKE \"%s%%\"" (tbl ()) uri
     in
-    ignore (Mysql.exec dbd (query tbl))
+    ignore (HMysql.exec dbd (query tbl))
   in
   List.iter del_from tables_to_clean