]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/metadata/extractor/extractor_manager.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / metadata / extractor / extractor_manager.ml
index 493868d540d4831c32713ea1a0b11c0295157272..05393b63e24980d97c31e2c73a9adcea5659c6ea 100644 (file)
@@ -1,4 +1,30 @@
+(* Copyright (C) 2004-2005, HELM Team.
+ * 
+ * This file is part of HELM, an Hypertextual, Electronic
+ * Library of Mathematics, developed at the Computer Science
+ * Department, University of Bologna, Italy.
+ * 
+ * HELM is free software; you can redistribute it and/or
+ * modify it under the terms of the GNU General Public License
+ * as published by the Free Software Foundation; either version 2
+ * of the License, or (at your option) any later version.
+ * 
+ * HELM is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License
+ * along with HELM; if not, write to the Free Software
+ * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
+ * MA  02111-1307, USA.
+ * 
+ * For details, see the HELM World-Wide-Web page,
+ * http://helm.cs.unibo.it/
+ *)
+
 (* HELPERS *)
+
 let create_all dbd =
   let obj_tbl = MetadataTypes.obj_tbl () in
   let sort_tbl = MetadataTypes.sort_tbl () in
@@ -126,7 +152,14 @@ let wait_a_peon peons =
   let pid,status = Unix.wait () in
   (match status with
   | Unix.WEXITED 0 -> ()
-  | _ -> prerr_endline (Printf.sprintf "PEON %d HAD A PROBLEM" pid));
+  | Unix.WEXITED s ->
+      prerr_endline (Printf.sprintf "PEON %d EXIT STATUS %d" pid s)
+  | Unix.WSIGNALED s -> 
+      prerr_endline 
+       (Printf.sprintf "PEON %d HAD A PROBLEM, KILLED BY SIGNAL %d" pid s)
+  | Unix.WSTOPPED s -> 
+      prerr_endline 
+       (Printf.sprintf "PEON %d HAD A PROBLEM, STOPPED BY %d" pid s));
   let p = fst(List.find (fun (_,x) -> x = pid) !peons) in
   peons := List.filter (fun (x,_) -> x <> p) !peons;
   peons := (p,0) :: !peons
@@ -139,7 +172,6 @@ let main () =
       Helm_registry.load_from "extractor.conf.xml";
       Http_getter.init ();
       print_endline "Updating the getter....";
-      Http_getter.update ();
       let base = (Helm_registry.get "tmp.dir") ^ "/maps" in
       let formats i = 
         (Helm_registry.get "tmp.dir") ^ "/"^(string_of_int i)^"/maps" 
@@ -188,8 +220,87 @@ let main () =
           wait_a_peon peons
       done;
       while is_a_peon_busy peons do wait_a_peon peons done;
-      print_string "END "; flush stdout;
-      ignore(Unix.system "date")
+      print_string "END "; flush stdout; 
+      ignore(Unix.system "date"); 
+      (* and now the rename table stuff *)
+      let obj_tbl = MetadataTypes.library_obj_tbl in
+      let sort_tbl = MetadataTypes.library_sort_tbl in
+      let rel_tbl = MetadataTypes.library_rel_tbl in
+      let name_tbl =  MetadataTypes.library_name_tbl in
+      let count_tbl = MetadataTypes.library_count_tbl in
+      let hits_tbl = MetadataTypes.library_hits_tbl in
+      let obj_tbl_b = obj_tbl ^ "_BACKUP" in     
+      let sort_tbl_b = sort_tbl ^ "_BACKUP" in     
+      let rel_tbl_b = rel_tbl ^ "_BACKUP" in
+      let name_tbl_b = name_tbl ^ "_BACKUP" in    
+      let count_tbl_b = count_tbl ^ "_BACKUP" in    
+      let obj_tbl_c = MetadataTypes.obj_tbl () in
+      let sort_tbl_c = MetadataTypes.sort_tbl () in
+      let rel_tbl_c = MetadataTypes.rel_tbl () in
+      let name_tbl_c =  MetadataTypes.name_tbl () in
+      let count_tbl_c = MetadataTypes.count_tbl () in
+      let stats = 
+        SqlStatements.drop_tables [
+          (obj_tbl_b,`RefObj);
+          (sort_tbl_b,`RefSort);
+          (rel_tbl_b,`RefRel);
+          (name_tbl_b,`ObjectName);
+          (count_tbl_b,`Count);
+          (hits_tbl,`Hits) ] @
+        SqlStatements.drop_indexes [
+          (obj_tbl,`RefObj);
+          (sort_tbl,`RefSort);
+          (rel_tbl,`RefRel);
+          (name_tbl,`ObjectName);
+          (count_tbl,`Count);
+          (obj_tbl_c,`RefObj);
+          (sort_tbl_c,`RefSort);
+          (rel_tbl_c,`RefRel);
+          (name_tbl_c,`ObjectName);
+          (count_tbl_c,`Count);
+          (hits_tbl,`Hits) ] @
+        SqlStatements.rename_tables [
+          (obj_tbl,obj_tbl_b);
+          (sort_tbl,sort_tbl_b);
+          (rel_tbl,rel_tbl_b);
+          (name_tbl,name_tbl_b);
+          (count_tbl,count_tbl_b) ] @
+        SqlStatements.rename_tables [
+          (obj_tbl_c,obj_tbl);
+          (sort_tbl_c,sort_tbl);
+          (rel_tbl_c,rel_tbl);
+          (name_tbl_c,name_tbl);
+          (count_tbl_c,count_tbl) ] @
+        SqlStatements.create_tables [
+          (hits_tbl,`Hits) ] @
+        SqlStatements.fill_hits obj_tbl hits_tbl @
+        SqlStatements.create_indexes [
+          (obj_tbl,`RefObj);
+          (sort_tbl,`RefSort);
+          (rel_tbl,`RefRel);
+          (name_tbl,`ObjectName);
+          (count_tbl,`Count);
+          (hits_tbl,`Hits) ]
+      in
+        List.iter (fun statement -> 
+          try
+(*            prerr_endline statement;*)
+            ignore (Mysql.exec dbd statement)
+          with exn -> 
+            let status = Mysql.status dbd in
+            match status with 
+            | Mysql.StatusError Mysql.Table_exists_error
+            | Mysql.StatusError Mysql.Bad_table_error
+            | Mysql.StatusError Mysql.Cant_drop_field_or_key
+            | Mysql.StatusError Mysql.Unknown_table -> ()
+            | Mysql.StatusError status ->
+(*                prerr_endline (string_of_int (Obj.magic status));*)
+                prerr_endline (Printexc.to_string exn);
+                raise exn
+            | _ ->
+                prerr_endline (Printexc.to_string exn);
+                ())
+        stats
 ;;
 
 main ()