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