]> matita.cs.unibo.it Git - helm.git/blob - helm/software/components/library/librarian.ml
f53de728c6a1ab554fed38f3bad8011c0d627f40
[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 baseuri_of_script ~include_paths file = 
83   let root, buri, path = find_root_for ~include_paths file in
84   let path = HExtlib.normalize_path path in
85   let root = HExtlib.normalize_path root in
86   let lpath = Str.split (Str.regexp "/") path in
87   let lroot = Str.split (Str.regexp "/") root in
88   let rec substract l1 l2 =
89     match l1, l2 with
90     | h1::tl1,h2::tl2 when h1 = h2 -> substract tl1 tl2
91     | l,[] -> l
92     | _ -> raise (NoRootFor (file ^" "^path^" "^root))
93   in
94   let extra_buri = substract lpath lroot in
95   let chop name = 
96     assert(Filename.check_suffix name ".ma" ||
97       Filename.check_suffix name ".mma");
98     try Filename.chop_extension name
99     with Invalid_argument "Filename.chop_extension" -> name
100   in
101   let extra = String.concat "/" extra_buri in
102    root,
103    remove_trailing_slash (HExtlib.normalize_path 
104     (buri ^ "/" ^ chop extra)),
105    path,
106    extra
107 ;;
108
109 let find_roots_in_dir dir =
110   HExtlib.find ~test:(fun f ->
111     Filename.basename f = "root" &&
112     try (Unix.stat f).Unix.st_kind = Unix.S_REG 
113     with Unix.Unix_error _ -> false)
114     dir
115 ;;
116
117 (* make *)
118 let load_deps_file f = 
119   let deps = ref [] in
120   let ic = open_in f in
121   try
122     while true do
123       begin
124         let l = input_line ic in
125         match Str.split (Str.regexp " ") l with
126         | [] -> 
127             HLog.error ("Malformed deps file: " ^ f); 
128             raise (Failure ("Malformed deps file: " ^ f)) 
129         | he::tl -> deps := (he,tl) :: !deps
130       end
131     done; !deps
132     with End_of_file -> !deps
133 ;;
134
135 type options = (string * string) list
136
137 module type Format =
138   sig
139     type source_object
140     type target_object
141     val load_deps_file: string -> (source_object * source_object list) list
142     val string_of_source_object: source_object -> string
143     val string_of_target_object: target_object -> string
144     val build: options -> source_object -> bool
145     val root_and_target_of: 
146           options -> source_object -> string option * target_object
147     val mtime_of_source_object: source_object -> float option
148     val mtime_of_target_object: target_object -> float option
149   end
150
151 module Make = functor (F:Format) -> struct
152
153   let say s = if debug then prerr_endline ("make: "^s);; 
154
155   let unopt_or_call x f y = match x with Some _ -> x | None -> f y;;
156
157   let younger_s_t (_,cs,ct) a b = 
158     let a = try Hashtbl.find cs a with Not_found -> assert false in
159     let b = 
160       try
161         match Hashtbl.find ct b with
162         | Some _ as x -> x
163         | None ->
164            match F.mtime_of_target_object b with
165            | Some t as x -> Hashtbl.add ct b x; x
166            | x -> x
167       with Not_found -> assert false
168     in
169     match a, b with 
170     | Some a, Some b -> a < b
171     | _ -> false
172   ;;
173
174   let younger_t_t (_,_,ct) a b = 
175     let a = 
176       try
177         match Hashtbl.find ct a with
178         | Some _ as x -> x
179         | None ->
180            match F.mtime_of_target_object a with
181            | Some t as x -> Hashtbl.add ct a x; x
182            | x -> x
183       with Not_found -> assert false
184     in
185     let b = 
186       try
187         match Hashtbl.find ct b with
188         | Some _ as x -> x
189         | None ->
190            match F.mtime_of_target_object b with
191            | Some t as x -> Hashtbl.add ct b x; x
192            | x -> x
193       with Not_found -> assert false
194     in
195     match a, b with
196     | Some a, Some b -> a < b
197     | _ -> false
198   ;;
199
200   let is_built opts t tgt = 
201     younger_s_t opts t tgt
202   ;;
203
204   let assoc4 l k = List.find (fun (k1,_,_,_) -> k1 = k) l;;
205
206   let fst4 = function (x,_,_,_) -> x;;
207
208   let rec needs_build opts deps compiled (t,dependencies,root,tgt) =
209     say ("Checking if "^F.string_of_source_object t^ " needs to be built");
210     if List.mem t compiled then
211       (say "already compiled"; false)
212     else
213     if not (is_built opts t tgt) then
214       (say(F.string_of_source_object t^" is not built, thus needs to be built");
215       true)
216     else
217     try
218       let unsat =
219         List.find
220           (needs_build opts deps compiled) 
221           (List.map (assoc4 deps) dependencies)
222       in
223         say (F.string_of_source_object t^" depends on "^
224          F.string_of_source_object (fst4 unsat)^
225          " that needs to be built, thus needs to be built");
226         true
227     with Not_found ->
228       try 
229         let _,_,_,unsat = 
230           List.find 
231            (fun (_,_,_,tgt1) -> younger_t_t opts tgt tgt1) 
232            (List.map (assoc4 deps) dependencies)
233         in
234           say 
235            (F.string_of_source_object t^" depends on "^F.string_of_target_object
236            unsat^" and "^F.string_of_source_object t^".o is younger than "^
237            F.string_of_target_object unsat^", thus needs to be built");
238           true
239       with Not_found -> false
240   ;;
241
242   let is_buildable opts compiled deps (t,dependencies,root,tgt as what) =
243     say ("Checking if "^F.string_of_source_object t^" is buildable");
244     let b = needs_build opts deps compiled what in
245     if not b then
246       (say (F.string_of_source_object t^
247        " does not need to be built, thus it not buildable");
248       false)
249     else
250     try  
251       let unsat,_,_,_ =
252         List.find (needs_build opts deps compiled) 
253           (List.map (assoc4 deps) dependencies)
254       in
255         say (F.string_of_source_object t^" depends on "^
256           F.string_of_source_object unsat^
257           " that needs build, thus is not buildable");
258         false
259     with Not_found -> 
260       say 
261         ("None of "^F.string_of_source_object t^
262         " dependencies needs to be built, thus it is buildable");
263       true
264   ;;
265
266   let rec purge_unwanted_roots wanted deps =
267     let roots, rest = 
268        List.partition 
269          (fun (t,d,_,_) ->
270            not (List.exists (fun (_,d1,_,_) -> List.mem t d1) deps))
271          deps
272     in
273     let newroots = List.filter (fun (t,_,_,_) -> List.mem t wanted) roots in
274     if newroots = roots then
275       deps
276     else
277       purge_unwanted_roots wanted (newroots @ rest)
278   ;;
279
280   let rec make_aux root (lo,_,ct as opts) compiled failed deps = 
281     let todo = List.filter (is_buildable opts compiled deps) deps in
282     let todo = List.filter (fun (f,_,_,_)->not (List.mem f failed)) todo in
283     if todo <> [] then
284       let compiled, failed = 
285         let todo =
286           let local, remote =
287             List.partition (fun (_,_,froot,_) -> froot = Some root) todo
288           in
289           remote @ local
290         in
291         List.fold_left 
292           (fun (c,f) (file,_,froot,tgt) ->
293             let rc = 
294               match froot with
295               | Some froot when froot = root -> 
296                   Hashtbl.remove ct tgt;
297                   Hashtbl.add ct tgt None;
298                   F.build lo file 
299               | Some froot -> make froot [file]
300               | None -> 
301                   HLog.error ("No root for: "^F.string_of_source_object file);
302                   false
303             in
304             if rc then (file::c,f)
305             else (c,file::f))
306           (compiled,failed) todo
307       in
308         make_aux root opts compiled failed deps
309     else
310       compiled, failed
311
312   and  make root targets = 
313     HLog.debug ("Entering directory '"^root^"'");
314     let old_root = Sys.getcwd () in
315     Sys.chdir root;
316     let deps = F.load_deps_file (root^"/depends") in
317     let local_options = load_root_file (root^"/root") in
318     let caches,cachet = Hashtbl.create 73, Hashtbl.create 73 in
319     (* deps are enriched with these informations to sped up things later *)
320     let deps = 
321       List.map 
322         (fun (file,d) -> 
323           let r,tgt = F.root_and_target_of local_options file in
324           Hashtbl.add caches file (F.mtime_of_source_object file);
325           Hashtbl.add cachet tgt (F.mtime_of_target_object tgt); 
326           file, d, r, tgt)
327         deps
328     in
329     let opts = local_options, caches, cachet in
330     let _compiled, failed =
331       if targets = [] then 
332         make_aux root opts [] [] deps
333       else
334         make_aux root opts [] [] (purge_unwanted_roots targets deps)
335     in
336     HLog.debug ("Leaving directory '"^root^"'");
337     Sys.chdir old_root;
338     failed = []
339   ;;
340
341 end
342   
343 let write_deps_file root deps =
344   let oc = open_out (root ^ "/depends") in
345   List.iter 
346     (fun (t,d) -> output_string oc (t^" "^String.concat " " d^"\n")) 
347     deps;
348   close_out oc;
349   HLog.message ("Generated: " ^ root ^ "/depends")
350 ;;
351