]> matita.cs.unibo.it Git - helm.git/blob - helm/software/components/library/librarian.ml
librarian: retrieval of buildable files speeded up a lot
[helm.git] / helm / software / components / library / librarian.ml
1 (* Copyright (C) 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 let timestamp msg =
27    let times = Unix.times () in
28    let msg = Printf.sprintf "UTIMESTAMP (%s): %f" msg times.Unix.tms_utime in
29    prerr_endline msg
30
31 let debug = false;;
32
33 exception NoRootFor of string
34
35 let absolutize path =
36  let path = 
37    if String.length path > 0 && path.[0] <> '/' then
38      Sys.getcwd () ^ "/" ^ path
39    else 
40      path
41  in
42    HExtlib.normalize_path path
43 ;;
44
45
46 let find_root path =
47   let path = absolutize path in
48   let paths = List.rev (Str.split (Str.regexp "/") path) in
49   let rec build = function
50     | he::tl as l -> ("/" ^ String.concat "/" (List.rev l) ^ "/") :: build tl
51     | [] -> ["/"]
52   in
53   let paths = List.map HExtlib.normalize_path (build paths) in
54   try HExtlib.find_in paths "root"
55   with Failure "find_in" -> 
56     raise (NoRootFor (path ^ " (" ^ String.concat ", " paths ^ ")"))
57 ;;
58   
59 let ensure_trailing_slash s = 
60   if s = "" then "/" else
61   if s.[String.length s-1] <> '/' then s^"/" else s
62 ;;
63
64 let remove_trailing_slash s = 
65   if s = "" then "" else
66   let len = String.length s in
67   if s.[len-1] = '/' then String.sub s 0 (len-1) else s
68 ;;
69
70 let load_root_file rootpath =
71   let data = HExtlib.input_file rootpath in
72   let lines = Str.split (Str.regexp "\n") data in
73   let clean s = 
74     Pcre.replace ~pat:"[ \t]+" ~templ:" "
75       (Pcre.replace ~pat:"^ *" (Pcre.replace ~pat:" *$" s))
76   in
77   List.map 
78     (fun l -> 
79       match Str.split (Str.regexp "=") l with
80       | [k;v] -> clean k, Http_getter_misc.strip_trailing_slash (clean v)
81       | _ -> raise (Failure ("Malformed root file: " ^ rootpath)))
82     lines
83 ;;
84
85 let find_root_for ~include_paths file = 
86  let include_paths = "" :: Sys.getcwd () :: include_paths in
87  try 
88    let path = HExtlib.find_in include_paths file in
89    let path = absolutize path in
90 (*     HLog.debug ("file "^file^" resolved as "^path);  *)
91    let rootpath, root, buri = 
92      try
93        let mburi = Helm_registry.get "matita.baseuri" in
94        match Str.split (Str.regexp " ") mburi with
95        | [root; buri] when HExtlib.is_prefix_of root path -> 
96            ":registry:", root, buri
97        | _ -> raise (Helm_registry.Key_not_found "matita.baseuri")
98      with Helm_registry.Key_not_found "matita.baseuri" -> 
99        let rootpath = find_root path in
100        let buri = List.assoc "baseuri" (load_root_file rootpath) in
101        rootpath, Filename.dirname rootpath, buri
102    in
103 (*     HLog.debug ("file "^file^" rooted by "^rootpath^"");  *)
104    let uri = Http_getter_misc.strip_trailing_slash buri in
105    if String.length uri < 5 || String.sub uri 0 5 <> "cic:/" then
106      HLog.error (rootpath ^ " sets an incorrect baseuri: " ^ buri);
107    ensure_trailing_slash root, remove_trailing_slash uri, path
108  with Failure "find_in" -> 
109    HLog.error ("We are in: " ^ Sys.getcwd ());
110    HLog.error ("Unable to find: "^file^"\nPaths explored:");
111    List.iter (fun x -> HLog.error (" - "^x)) include_paths;
112    raise (NoRootFor file)
113 ;;
114
115 let mk_baseuri root extra =
116   let chop name = 
117     assert(Filename.check_suffix name ".ma" ||
118       Filename.check_suffix name ".mma");
119     try Filename.chop_extension name
120     with Invalid_argument "Filename.chop_extension" -> name
121   in
122    remove_trailing_slash (HExtlib.normalize_path (root ^ "/" ^ chop extra))
123 ;;
124
125 let baseuri_of_script ~include_paths file = 
126   let root, buri, path = find_root_for ~include_paths file in
127   let path = HExtlib.normalize_path path in
128   let root = HExtlib.normalize_path root in
129   let lpath = Str.split (Str.regexp "/") path in
130   let lroot = Str.split (Str.regexp "/") root in
131   let rec substract l1 l2 =
132     match l1, l2 with
133     | h1::tl1,h2::tl2 when h1 = h2 -> substract tl1 tl2
134     | l,[] -> l
135     | _ -> raise (NoRootFor (file ^" "^path^" "^root))
136   in
137   let extra_buri = substract lpath lroot in
138   let extra = String.concat "/" extra_buri in
139    root,
140    mk_baseuri buri extra,
141    path,
142    extra
143 ;;
144
145 let find_roots_in_dir dir =
146   HExtlib.find ~test:(fun f ->
147     Filename.basename f = "root" &&
148     try (Unix.stat f).Unix.st_kind = Unix.S_REG 
149     with Unix.Unix_error _ -> false)
150     dir
151 ;;
152
153 (* make *)
154 let load_deps_file f = 
155   let deps = ref [] in
156   let ic = open_in f in
157   try
158     while true do
159       begin
160         let l = input_line ic in
161         match Str.split (Str.regexp " ") l with
162         | [] -> 
163             HLog.error ("Malformed deps file: " ^ f); 
164             raise (Failure ("Malformed deps file: " ^ f)) 
165         | he::tl -> deps := (he,tl) :: !deps
166       end
167     done; !deps
168     with End_of_file -> !deps
169 ;;
170
171 type options = (string * string) list
172
173 module type Format =
174   sig
175     type source_object
176     type target_object
177     val load_deps_file: string -> (source_object * source_object list) list
178     val string_of_source_object: source_object -> string
179     val string_of_target_object: target_object -> string
180     val build: options -> source_object -> bool
181     val root_and_target_of: 
182           options -> source_object -> string option * target_object
183     val mtime_of_source_object: source_object -> float option
184     val mtime_of_target_object: target_object -> float option
185     val is_readonly_buri_of: options -> source_object -> bool
186   end
187
188 module Make = functor (F:Format) -> struct
189
190   type status = Done of bool
191               | Ready of bool
192
193   let say s = if debug then prerr_endline ("make: "^s);; 
194
195   let unopt_or_call x f y = match x with Some _ -> x | None -> f y;;
196
197   let fst4 = function (x,_,_,_) -> x;;
198
199   let younger_s_t (_,cs, ct, _, _) a b = 
200     let a = try Hashtbl.find cs a with Not_found -> assert false in
201     let b = 
202       try
203         match Hashtbl.find ct b with
204         | Some _ as x -> x
205         | None ->
206            match F.mtime_of_target_object b with
207            | Some t as x -> 
208                Hashtbl.remove ct b;
209                Hashtbl.add ct b x; x
210            | x -> x
211       with Not_found -> assert false
212     in
213     match a, b with 
214     | Some a, Some b -> a < b
215     | _ -> false
216   ;;
217
218   let younger_t_t (_,_,ct, _, _) a b = 
219     let a = 
220       try
221         match Hashtbl.find ct a with
222         | Some _ as x -> x
223         | None ->
224            match F.mtime_of_target_object a with
225            | Some t as x -> 
226                Hashtbl.remove ct b;
227                Hashtbl.add ct a x; x
228            | x -> x
229       with Not_found -> assert false
230     in
231     let b = 
232       try
233         match Hashtbl.find ct b with
234         | Some _ as x -> x
235         | None ->
236            match F.mtime_of_target_object b with
237            | Some t as x -> 
238                Hashtbl.remove ct b;
239                Hashtbl.add ct b x; x
240            | x -> x
241       with Not_found -> assert false
242     in
243     match a, b with
244     | Some a, Some b -> a < b
245     | _ -> false
246   ;;
247
248   let rec purge_unwanted_roots wanted deps =
249     let roots, rest = 
250        List.partition 
251          (fun (t,d,_,_) ->
252            not (List.exists (fun (_,d1,_,_) -> List.mem t d1) deps))
253          deps
254     in
255     let newroots = List.filter (fun (t,_,_,_) -> List.mem t wanted) roots in
256     if newroots = roots then
257       deps
258     else
259       purge_unwanted_roots wanted (newroots @ rest)
260   ;;
261
262   let is_not_ro (opts,_,_,_,_) (f,_,r,_) =
263     match r with
264     | Some root -> not (F.is_readonly_buri_of opts f)
265     | None -> assert false
266   ;;
267
268   let rec get_status opts what =
269      let _, _, _, cc, cd = opts in
270      let t, dependencies, root, tgt = what in
271      try Done (Hashtbl.find cc t)
272 (* say "already built" *)
273      with Not_found ->
274         let map st d = match st with
275            | Done false  -> st
276            | Ready false -> st
277            | _           ->
278               let whatd = Hashtbl.find cd d in
279               let _, _, _, tgtd = whatd in
280               begin match st, get_status opts whatd with
281                  | _, Done false         -> Hashtbl.add cc t false; Done false
282                  | Done true, Done true  -> 
283                     if younger_t_t opts tgt tgtd then Ready true else Done true  
284 (* say (F.string_of_source_object t^" depends on "^F.string_of_target_object unsat^" and "^F.string_of_source_object t^".o is younger than "^ F.string_of_target_object unsat^", thus needs to be built") *)
285                  | Done true, Ready _    -> Ready false
286                  | Ready true, Ready _   -> Ready false
287 (* say (F.string_of_source_object t^" depends on "^ F.string_of_source_object (fst4 unsat)^ " that is not built, thus is not ready") *)
288                  | Ready true, Done true -> Ready true
289                  | _                     -> st
290               end
291         in
292         let st = if younger_s_t opts t tgt then Done true else Ready true in
293         match List.fold_left map st dependencies with
294            | Done true -> Hashtbl.add cc t true; Done true
295 (* say(F.string_of_source_object t^" is built" *)
296            | st     -> st
297
298   let list_partition_filter_rev filter l =
299      let rec aux l1 l2 = function
300         | []       -> l1, l2
301         | hd :: tl ->
302            begin match filter hd with
303               | None       -> aux l1 l2 tl
304               | Some true  -> aux (hd :: l1) l2 tl
305               | Some false -> aux l1 (hd :: l2) tl
306            end
307      in
308      aux [] [] l
309
310   let rec make_aux root (lo,_,ct, cc, _ as opts) ok deps = 
311     timestamp "filter get_status: begin";
312     let map what = match get_status opts what with
313        | Done _  -> None
314        | Ready b -> Some b
315     in
316     let todo, deps = list_partition_filter_rev map deps in
317     timestamp "filter get_status: end";
318     let todo =
319       let local, remote =
320         List.partition (fun (_,_,froot,_) -> froot = Some root) todo
321       in
322       let local, skipped = List.partition (is_not_ro opts) local in
323       List.iter 
324        (fun x -> 
325         HLog.warn("Read only baseuri for: "^F.string_of_source_object(fst4 x)))
326        skipped;
327       remote @ local
328     in
329     if todo <> [] then begin
330        let ok = List.fold_left  
331           (fun ok (file,_,froot,tgt) ->
332             let rc = 
333               match froot with
334               | Some froot when froot = root -> 
335                   Hashtbl.remove ct tgt;
336                   Hashtbl.add ct tgt None;
337                   timestamp "building";
338                   let r = F.build lo file in
339                   timestamp "done"; r
340               | Some froot -> make froot [file]
341               | None -> 
342                   HLog.error ("No root for: "^F.string_of_source_object file);
343                   false
344             in
345             Hashtbl.add cc file rc;
346             ok && rc 
347           )
348           ok (List.rev todo)
349        in
350       make_aux root opts ok (List.rev deps)
351     end
352     else
353       ok
354
355   and  make root targets = 
356     timestamp "entering";
357     HLog.debug ("Entering directory '"^root^"'");
358     let old_root = Sys.getcwd () in
359     Sys.chdir root;
360     let deps = F.load_deps_file (root^"/depends") in
361     let local_options = load_root_file (root^"/root") in
362     let caches,cachet,cachec,cached = 
363        Hashtbl.create 73, Hashtbl.create 73, Hashtbl.create 73, Hashtbl.create 73
364     in
365     (* deps are enriched with these informations to sped up things later *)
366     let deps = 
367       List.map 
368         (fun (file,d) -> 
369           let r,tgt = F.root_and_target_of local_options file in
370           Hashtbl.add caches file (F.mtime_of_source_object file);
371           Hashtbl.add cachet tgt (F.mtime_of_target_object tgt); 
372           Hashtbl.add cached file (file, d, r, tgt);
373           (file, d, r, tgt)
374         )
375         deps
376     in
377     let opts = local_options, caches, cachet, cachec, cached in
378     let ok =
379       if targets = [] then 
380         make_aux root opts true deps
381       else
382         make_aux root opts true 
383           (purge_unwanted_roots targets deps)
384     in
385     HLog.debug ("Leaving directory '"^root^"'");
386     Sys.chdir old_root;
387     timestamp "leaving";
388     ok
389   ;;
390
391 end
392   
393 let write_deps_file where deps = match where with 
394    | Some root ->
395       let oc = open_out (root ^ "/depends") in
396       let map (t, d) = output_string oc (t^" "^String.concat " " d^"\n") in
397       List.iter map deps; close_out oc;
398       HLog.message ("Generated: " ^ root ^ "/depends")
399    | None -> 
400       print_endline (String.concat " " (List.flatten (List.map snd deps)))
401       
402 (* FG ***********************************************************************)
403
404 (* scheme uri part as defined in URI Generic Syntax (RFC 3986) *)
405 let uri_scheme_rex = Pcre.regexp "^[[:alpha:]][[:alnum:]\-+.]*:"
406
407 let is_uri str =
408    Pcre.pmatch ~rex:uri_scheme_rex str