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