]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/metadata/extractor/extractor_manager.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / metadata / extractor / extractor_manager.ml
1 (* Copyright (C) 2004-2005, 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 (* HELPERS *)
27
28 let create_all dbd =
29   let obj_tbl = MetadataTypes.obj_tbl () in
30   let sort_tbl = MetadataTypes.sort_tbl () in
31   let rel_tbl = MetadataTypes.rel_tbl () in
32   let name_tbl =  MetadataTypes.name_tbl () in
33   let count_tbl = MetadataTypes.count_tbl () in
34   let tbls = [ 
35     (obj_tbl,`RefObj) ; (sort_tbl,`RefSort) ; (rel_tbl,`RefRel) ;
36     (name_tbl,`ObjectName) ; (count_tbl,`Count) ] 
37   in
38   let statements = 
39     (SqlStatements.create_tables tbls) @ (SqlStatements.create_indexes tbls)
40   in
41   List.iter (fun statement -> 
42     try
43       ignore (Mysql.exec dbd statement)
44     with
45       exn -> 
46          let status = Mysql.status dbd in
47          match status with 
48          | Mysql.StatusError Mysql.Table_exists_error -> ()
49          | Mysql.StatusError _ -> raise exn
50          | _ -> ()
51       ) statements
52
53 let drop_all dbd =
54   let obj_tbl = MetadataTypes.obj_tbl () in
55   let sort_tbl = MetadataTypes.sort_tbl () in
56   let rel_tbl = MetadataTypes.rel_tbl () in
57   let name_tbl =  MetadataTypes.name_tbl () in
58   let count_tbl = MetadataTypes.count_tbl () in
59   let tbls = [ 
60     (obj_tbl,`RefObj) ; (sort_tbl,`RefSort) ; (rel_tbl,`RefRel) ;
61     (name_tbl,`ObjectName) ; (count_tbl,`Count) ] 
62   in
63   let statements = 
64     (SqlStatements.drop_tables tbls) @ (SqlStatements.drop_indexes tbls)
65   in
66   List.iter (fun statement -> 
67     try
68       ignore (Mysql.exec dbd statement)
69     with Mysql.Error _ as exn ->
70       match Mysql.errno dbd with 
71       | Mysql.Bad_table_error 
72       | Mysql.No_such_index | Mysql.No_such_table -> () 
73       | _ -> raise exn
74     ) statements
75   
76 let slash_RE = Str.regexp "/"
77     
78 let partition l = 
79   let l = List.fast_sort Pervasives.compare l in
80   let matches s1 s2 =
81     let l1,l2 = Str.split slash_RE s1, Str.split slash_RE s2 in
82     match l1,l2 with
83     | _::x::_,_::y::_ -> x = y 
84     | _ -> false
85   in
86   let rec chunk l =
87     match l with
88     | [] -> [],[]
89     | h::(h1::tl as rest) when matches h h1 -> 
90         let ch,todo = chunk rest in
91         (h::ch),todo
92     | h::(h1::tl as rest)-> [h],rest
93     | h::_ -> [h],[]
94   in
95   let rec split l = 
96     let ch, todo = chunk l in
97     match todo with
98     | [] -> [ch]
99     | _ -> ch :: split todo
100   in
101   split l
102   
103     
104 (* ARGV PARSING *)
105
106 let _ = 
107   try
108   if Sys.argv.(1) = "-h"||Sys.argv.(1) = "-help"||Sys.argv.(1) = "--help" then
109     begin
110     prerr_endline "
111 usage: ./extractor_manager[.opt] [processes] [owner]
112
113 defaults:
114   processes = 2
115   owner = NEW
116
117 "; 
118     exit 1
119     end
120   with Invalid_argument _ -> ()
121
122 let processes = 
123   try
124     int_of_string (Sys.argv.(1))
125   with 
126     Invalid_argument _ -> 2
127
128 let owner =
129   try
130     Sys.argv.(2)
131   with Invalid_argument _ -> "NEW"
132
133 let create_peons i =
134   let rec aux = function
135     | 0 -> []
136     | n -> (n,0) :: aux (n-1)
137   in
138   ref (aux i)
139
140 let is_a_peon_idle peons =
141   List.exists (fun (_,x) -> x = 0) !peons
142
143 let get_ide_peon peons =
144   let p = fst(List.find (fun (_,x) -> x = 0) !peons) in
145   peons := List.filter (fun (x,_) -> x <> p) !peons;
146   p
147  
148 let assign_peon peon pid peons =
149   peons := (peon,pid) :: !peons
150   
151 let wait_a_peon peons =
152   let pid,status = Unix.wait () in
153   (match status with
154   | Unix.WEXITED 0 -> ()
155   | Unix.WEXITED s ->
156       prerr_endline (Printf.sprintf "PEON %d EXIT STATUS %d" pid s)
157   | Unix.WSIGNALED s -> 
158       prerr_endline 
159        (Printf.sprintf "PEON %d HAD A PROBLEM, KILLED BY SIGNAL %d" pid s)
160   | Unix.WSTOPPED s -> 
161       prerr_endline 
162        (Printf.sprintf "PEON %d HAD A PROBLEM, STOPPED BY %d" pid s));
163   let p = fst(List.find (fun (_,x) -> x = pid) !peons) in
164   peons := List.filter (fun (x,_) -> x <> p) !peons;
165   peons := (p,0) :: !peons
166  
167 let is_a_peon_busy peons =
168   List.exists (fun (_,x) -> x <> 0) !peons
169   
170 (* MAIN *)
171 let main () =
172       Helm_registry.load_from "extractor.conf.xml";
173       Http_getter.init ();
174       print_endline "Updating the getter....";
175       let base = (Helm_registry.get "tmp.dir") ^ "/maps" in
176       let formats i = 
177         (Helm_registry.get "tmp.dir") ^ "/"^(string_of_int i)^"/maps" 
178       in
179       for i = 1 to processes do
180         let fmt = formats i in
181         ignore(Unix.system ("rm -rf " ^ fmt));
182         ignore(Unix.system ("mkdir -p " ^ fmt));
183         ignore(Unix.system ("cp -r " ^ base ^ " " ^ fmt ^ "/../"));
184       done;
185       let dbd =
186         Mysql.quick_connect 
187           ~host:(Helm_registry.get "db.host") 
188           ~user:(Helm_registry.get "db.user") 
189           ~database:(Helm_registry.get "db.database") ()
190       in
191       MetadataTypes.ownerize_tables owner;
192       let uri_RE = Str.regexp ".*\\(ind\\|var\\|con\\)$" in
193       drop_all dbd;
194       create_all dbd;
195       let uris = Http_getter.getalluris () in
196       let uris = List.filter (fun u -> Str.string_match uri_RE u 0) uris in
197       let todo = partition uris in
198       let cur = ref 0 in
199       let tot = List.length todo in
200       let peons = create_peons processes in
201       print_string "START "; flush stdout;
202       ignore(Unix.system "date");
203       while !cur < tot do
204         if is_a_peon_idle peons then
205           let peon = get_ide_peon peons in
206           let fmt = formats peon in
207           let oc = open_out (fmt ^ "/../todo") in
208           List.iter (fun s -> output_string oc (s^"\n")) (List.nth todo !cur);
209           close_out oc;
210           let pid = Unix.fork () in
211           if pid = 0 then
212             Unix.execv 
213               "./extractor.opt" [| "./extractor.opt" ; fmt ^ "/../" ; owner|]
214           else
215             begin
216               assign_peon peon pid peons;
217               incr cur
218             end
219         else
220           wait_a_peon peons
221       done;
222       while is_a_peon_busy peons do wait_a_peon peons done;
223       print_string "END "; flush stdout; 
224       ignore(Unix.system "date"); 
225       (* and now the rename table stuff *)
226       let obj_tbl = MetadataTypes.library_obj_tbl in
227       let sort_tbl = MetadataTypes.library_sort_tbl in
228       let rel_tbl = MetadataTypes.library_rel_tbl in
229       let name_tbl =  MetadataTypes.library_name_tbl in
230       let count_tbl = MetadataTypes.library_count_tbl in
231       let hits_tbl = MetadataTypes.library_hits_tbl in
232       let obj_tbl_b = obj_tbl ^ "_BACKUP" in     
233       let sort_tbl_b = sort_tbl ^ "_BACKUP" in     
234       let rel_tbl_b = rel_tbl ^ "_BACKUP" in
235       let name_tbl_b = name_tbl ^ "_BACKUP" in    
236       let count_tbl_b = count_tbl ^ "_BACKUP" in    
237       let obj_tbl_c = MetadataTypes.obj_tbl () in
238       let sort_tbl_c = MetadataTypes.sort_tbl () in
239       let rel_tbl_c = MetadataTypes.rel_tbl () in
240       let name_tbl_c =  MetadataTypes.name_tbl () in
241       let count_tbl_c = MetadataTypes.count_tbl () in
242       let stats = 
243         SqlStatements.drop_tables [
244           (obj_tbl_b,`RefObj);
245           (sort_tbl_b,`RefSort);
246           (rel_tbl_b,`RefRel);
247           (name_tbl_b,`ObjectName);
248           (count_tbl_b,`Count);
249           (hits_tbl,`Hits) ] @
250         SqlStatements.drop_indexes [
251           (obj_tbl,`RefObj);
252           (sort_tbl,`RefSort);
253           (rel_tbl,`RefRel);
254           (name_tbl,`ObjectName);
255           (count_tbl,`Count);
256           (obj_tbl_c,`RefObj);
257           (sort_tbl_c,`RefSort);
258           (rel_tbl_c,`RefRel);
259           (name_tbl_c,`ObjectName);
260           (count_tbl_c,`Count);
261           (hits_tbl,`Hits) ] @
262         SqlStatements.rename_tables [
263           (obj_tbl,obj_tbl_b);
264           (sort_tbl,sort_tbl_b);
265           (rel_tbl,rel_tbl_b);
266           (name_tbl,name_tbl_b);
267           (count_tbl,count_tbl_b) ] @
268         SqlStatements.rename_tables [
269           (obj_tbl_c,obj_tbl);
270           (sort_tbl_c,sort_tbl);
271           (rel_tbl_c,rel_tbl);
272           (name_tbl_c,name_tbl);
273           (count_tbl_c,count_tbl) ] @
274         SqlStatements.create_tables [
275           (hits_tbl,`Hits) ] @
276         SqlStatements.fill_hits obj_tbl hits_tbl @
277         SqlStatements.create_indexes [
278           (obj_tbl,`RefObj);
279           (sort_tbl,`RefSort);
280           (rel_tbl,`RefRel);
281           (name_tbl,`ObjectName);
282           (count_tbl,`Count);
283           (hits_tbl,`Hits) ]
284       in
285         List.iter (fun statement -> 
286           try
287 (*            prerr_endline statement;*)
288             ignore (Mysql.exec dbd statement)
289           with exn -> 
290             let status = Mysql.status dbd in
291             match status with 
292             | Mysql.StatusError Mysql.Table_exists_error
293             | Mysql.StatusError Mysql.Bad_table_error
294             | Mysql.StatusError Mysql.Cant_drop_field_or_key
295             | Mysql.StatusError Mysql.Unknown_table -> ()
296             | Mysql.StatusError status ->
297 (*                prerr_endline (string_of_int (Obj.magic status));*)
298                 prerr_endline (Printexc.to_string exn);
299                 raise exn
300             | _ ->
301                 prerr_endline (Printexc.to_string exn);
302                 ())
303         stats
304 ;;
305
306 main ()