]> matita.cs.unibo.it Git - helm.git/blob - helm/software/components/library/librarian.ml
BIG FAT WARNING: DEVELOPMENTS DIE HERE
[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 prerr_endline 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 a fa b fb = 
158     let a = unopt_or_call a F.mtime_of_source_object fa in
159     let b = unopt_or_call b F.mtime_of_target_object fb in
160     match a,b with 
161     | Some a, Some b -> a < b
162     | _ -> false
163   ;;
164
165   let younger_t_t a fa b fb = 
166     let a = unopt_or_call a F.mtime_of_target_object fa in
167     let b = unopt_or_call b F.mtime_of_target_object fb in
168     match a, b with
169     | Some a, Some b -> a < b
170     | _ -> false
171   ;;
172
173   let is_built opts mt t mtgt tgt = 
174     younger_s_t mt t mtgt tgt
175   ;;
176
177   let assoc6 l k = List.find (fun (k1,_,_,_,_,_) -> k1 = k) l;;
178
179   let fst6 = function (x,_,_,_,_,_) -> x;;
180
181   let rec needs_build opts deps compiled (t,dependencies,root,tgt,mt,mtgt) =
182     prerr_endline ("Checking if "^F.string_of_source_object t^
183       " needs to be built");
184     if List.mem t compiled then
185       (prerr_endline "already compiled";
186       false)
187     else
188     if not (is_built opts mt t mtgt tgt) then
189       (prerr_endline (F.string_of_source_object t^
190        " is not built, thus needs to be built");
191       true)
192     else
193     try
194       let unsat =
195         List.find
196           (needs_build opts deps compiled) 
197           (List.map (assoc6 deps) dependencies)
198       in
199         prerr_endline 
200          (F.string_of_source_object t^" depends on "^
201          F.string_of_source_object (fst6 unsat)^
202          " that needs to be built, thus needs to be built");
203         true
204     with Not_found ->
205       try 
206         let _,_,_,unsat,_,_ = 
207           List.find 
208            (fun (_,_,_,tgt1,_,mtgt1) -> younger_t_t mtgt tgt mtgt1 tgt1) 
209            (List.map (assoc6 deps) dependencies)
210         in
211           prerr_endline 
212            (F.string_of_source_object t^" depends on "^F.string_of_target_object
213            unsat^" and "^F.string_of_source_object t^".o is younger than "^
214            F.string_of_target_object unsat^", thus needs to be built");
215           true
216       with Not_found -> false
217   ;;
218
219   let is_buildable opts compiled deps (t,dependencies,root,tgt,_,_ as what) =
220     prerr_endline ("Checking if "^F.string_of_source_object t^" is buildable");
221     let b = needs_build opts deps compiled what in
222     if not b then
223       (prerr_endline (F.string_of_source_object t^
224        " does not need to be built, thus it not buildable");
225       false)
226     else
227     try  
228       let unsat,_,_,_,_,_ =
229         List.find (needs_build opts deps compiled) 
230           (List.map (assoc6 deps) dependencies)
231       in
232         prerr_endline 
233           (F.string_of_source_object t^" depends on "^
234           F.string_of_source_object unsat^
235           " that needs build, thus is not buildable");
236         false
237     with Not_found -> 
238       prerr_endline 
239         ("None of "^F.string_of_source_object t^
240         " dependencies needs to be built, thus it is buildable");
241       true
242   ;;
243
244   let rec purge_unwanted_roots wanted deps =
245     let roots, rest = 
246        List.partition 
247          (fun (t,d,_,_,_,_) ->
248            not (List.exists (fun (_,d1,_,_,_,_) -> List.mem t d1) deps))
249          deps
250     in
251     let newroots = List.filter (fun (t,_,_,_,_,_) -> List.mem t wanted) roots in
252     if newroots = roots then
253       deps
254     else
255       purge_unwanted_roots wanted (newroots @ rest)
256   ;;
257
258
259   let rec make_aux root local_options compiled failed deps = 
260     let todo = List.filter (is_buildable local_options compiled deps) deps in
261     let todo = List.filter (fun (f,_,_,_,_,_)->not (List.mem f failed)) todo in
262     if todo <> [] then
263       let compiled, failed = 
264         let todo =
265           let local, remote =
266             List.partition (fun (_,_,froot,_,_,_) -> froot = Some root) todo
267           in
268           remote @ local
269         in
270         List.fold_left 
271           (fun (c,f) (file,_,froot,_,_,_) ->
272             let rc = 
273               match froot with
274               | Some froot when froot = root ->
275                   F.build local_options file 
276               | Some froot ->
277                   make froot [file]
278               | None -> 
279                   HLog.error ("No root for: "^F.string_of_source_object file);
280                   false
281             in
282             if rc then (file::c,f)
283             else (c,file::f))
284           (compiled,failed) todo
285       in
286         make_aux root local_options compiled failed deps
287     else
288       compiled, failed
289
290   and  make root targets = 
291     HLog.debug ("Entering directory '"^root^"'");
292     let old_root = Sys.getcwd () in
293     Sys.chdir root;
294     let deps = F.load_deps_file (root^"/depends") in
295     let local_options = load_root_file (root^"/root") in
296     let deps = 
297       List.map 
298         (fun (file,d) -> 
299                 HLog.debug (F.string_of_source_object file);
300           let r,tgt = F.root_and_target_of local_options file in
301           file, d, r, tgt, F.mtime_of_source_object file, 
302           F.mtime_of_target_object tgt) 
303         deps
304     in
305     let _compiled, failed =
306       if targets = [] then 
307         make_aux root local_options [] [] deps
308       else
309         make_aux root local_options [] [] (purge_unwanted_roots targets deps)
310     in
311     HLog.debug ("Leaving directory '"^root^"'");
312     Sys.chdir old_root;
313     failed = []
314   ;;
315
316 end
317   
318 let write_deps_file root deps =
319   let oc = open_out (root ^ "/depends") in
320   List.iter 
321     (fun (t,d) -> output_string oc (t^" "^String.concat " " d^"\n")) 
322     deps;
323   close_out oc;
324   HLog.message ("Generated: " ^ root ^ "/depends")
325 ;;
326