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