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