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