]> matita.cs.unibo.it Git - helm.git/blob - helm/software/components/library/librarian.ml
lambda-delta: we added the support for position indexes in global references
[helm.git] / helm / software / components / library / librarian.ml
1 (* Copyright (C) 2005, HELM Team.
2  * 
3  * This file is part of HELM, an Hypertextual, Electronic
4  * Library of Mathematics, developed at the Computer Science
5  * Department, University of Bologna, Italy.
6  * 
7  * HELM is free software; you can redistribute it and/or
8  * modify it under the terms of the GNU General Public License
9  * as published by the Free Software Foundation; either version 2
10  * of the License, or (at your option) any later version.
11  * 
12  * HELM is distributed in the hope that it will be useful,
13  * but WITHOUT ANY WARRANTY; without even the implied warranty of
14  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15  * GNU General Public License for more details.
16  *
17  * You should have received a copy of the GNU General Public License
18  * along with HELM; if not, write to the Free Software
19  * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
20  * MA  02111-1307, USA.
21  * 
22  * For details, see the HELM World-Wide-Web page,
23  * http://helm.cs.unibo.it/
24  *)
25
26 let debug = false;;
27
28 let timestamp msg =
29    if debug then
30       let times = Unix.times () in
31       let utime = times.Unix.tms_utime in
32       let msg = Printf.sprintf "UTIMESTAMP (%s): %f" msg utime in
33       prerr_endline msg
34
35 exception NoRootFor of string
36
37 let absolutize path =
38  let path = 
39    if String.length path > 0 && path.[0] <> '/' then
40      Sys.getcwd () ^ "/" ^ path
41    else 
42      path
43  in
44    HExtlib.normalize_path path
45 ;;
46
47
48 let find_root path =
49   let path = absolutize path in
50   let paths = List.rev (Str.split (Str.regexp "/") path) in
51   let rec build = function
52     | he::tl as l -> ("/" ^ String.concat "/" (List.rev l) ^ "/") :: build tl
53     | [] -> ["/"]
54   in
55   let paths = List.map HExtlib.normalize_path (build paths) in
56   try HExtlib.find_in paths "root"
57   with Failure "find_in" -> 
58     raise (NoRootFor (path ^ " (" ^ String.concat ", " paths ^ ")"))
59 ;;
60   
61 let ensure_trailing_slash s = 
62   if s = "" then "/" else
63   if s.[String.length s-1] <> '/' then s^"/" else s
64 ;;
65
66 let remove_trailing_slash s = 
67   if s = "" then "" else
68   let len = String.length s in
69   if s.[len-1] = '/' then String.sub s 0 (len-1) else s
70 ;;
71
72 let load_root_file rootpath =
73   let data = HExtlib.input_file rootpath in
74   let lines = Str.split (Str.regexp "\n") data in
75   let clean s = 
76     Pcre.replace ~pat:"[ \t]+" ~templ:" "
77       (Pcre.replace ~pat:"^ *" (Pcre.replace ~pat:" *$" s))
78   in
79   List.map 
80     (fun l -> 
81       match Str.split (Str.regexp "=") l with
82       | [k;v] -> clean k, Http_getter_misc.strip_trailing_slash (clean v)
83       | _ -> raise (Failure ("Malformed root file: " ^ rootpath)))
84     lines
85 ;;
86
87 let find_root_for ~include_paths file = 
88  let include_paths = "" :: Sys.getcwd () :: include_paths in
89  try 
90    let path = HExtlib.find_in include_paths file in
91    let path = absolutize path in
92 (*     HLog.debug ("file "^file^" resolved as "^path);  *)
93    let rootpath, root, buri = 
94      try
95        let mburi = Helm_registry.get "matita.baseuri" in
96        match Str.split (Str.regexp " ") mburi with
97        | [root; buri] when HExtlib.is_prefix_of root path -> 
98            ":registry:", root, buri
99        | _ -> raise (Helm_registry.Key_not_found "matita.baseuri")
100      with Helm_registry.Key_not_found "matita.baseuri" -> 
101        let rootpath = find_root path in
102        let buri = List.assoc "baseuri" (load_root_file rootpath) in
103        rootpath, Filename.dirname rootpath, buri
104    in
105 (*     HLog.debug ("file "^file^" rooted by "^rootpath^"");  *)
106    let uri = Http_getter_misc.strip_trailing_slash buri in
107    if String.length uri < 5 || String.sub uri 0 5 <> "cic:/" then
108      HLog.error (rootpath ^ " sets an incorrect baseuri: " ^ buri);
109    ensure_trailing_slash root, remove_trailing_slash uri, path
110  with Failure "find_in" -> 
111    HLog.error ("We are in: " ^ Sys.getcwd ());
112    HLog.error ("Unable to find: "^file^"\nPaths explored:");
113    List.iter (fun x -> HLog.error (" - "^x)) include_paths;
114    raise (NoRootFor file)
115 ;;
116
117 let mk_baseuri root extra =
118   let chop name = 
119     assert(Filename.check_suffix name ".ma" ||
120       Filename.check_suffix name ".mma");
121     try Filename.chop_extension name
122     with Invalid_argument "Filename.chop_extension" -> name
123   in
124    remove_trailing_slash (HExtlib.normalize_path (root ^ "/" ^ chop extra))
125 ;;
126
127 let baseuri_of_script ~include_paths file = 
128   let root, buri, path = find_root_for ~include_paths file in
129   let path = HExtlib.normalize_path path in
130   let root = HExtlib.normalize_path root in
131   let lpath = Str.split (Str.regexp "/") path in
132   let lroot = Str.split (Str.regexp "/") root in
133   let rec substract l1 l2 =
134     match l1, l2 with
135     | h1::tl1,h2::tl2 when h1 = h2 -> substract tl1 tl2
136     | l,[] -> l
137     | _ -> raise (NoRootFor (file ^" "^path^" "^root))
138   in
139   let extra_buri = substract lpath lroot in
140   let extra = String.concat "/" extra_buri in
141    root,
142    mk_baseuri buri extra,
143    path,
144    extra
145 ;;
146
147 let find_roots_in_dir dir =
148   HExtlib.find ~test:(fun f ->
149     Filename.basename f = "root" &&
150     try (Unix.stat f).Unix.st_kind = Unix.S_REG 
151     with Unix.Unix_error _ -> false)
152     dir
153 ;;
154
155 (* make *)
156 let load_deps_file f = 
157   let deps = ref [] in
158   let ic = open_in f in
159   try
160     while true do
161       begin
162         let l = input_line ic in
163         match Str.split (Str.regexp " ") l with
164         | [] -> 
165             HLog.error ("Malformed deps file: " ^ f); 
166             raise (Failure ("Malformed deps file: " ^ f)) 
167         | he::tl -> deps := (he,tl) :: !deps
168       end
169     done; !deps
170     with End_of_file -> !deps
171 ;;
172
173 type options = (string * string) list
174
175 module type Format =
176   sig
177     type source_object
178     type target_object
179     val load_deps_file: string -> (source_object * source_object list) list
180     val string_of_source_object: source_object -> string
181     val string_of_target_object: target_object -> string
182     val build: options -> source_object -> bool
183     val root_and_target_of: 
184           options -> source_object -> string option * target_object
185     val mtime_of_source_object: source_object -> float option
186     val mtime_of_target_object: target_object -> float option
187     val is_readonly_buri_of: options -> source_object -> bool
188   end
189
190 module Make = functor (F:Format) -> struct
191
192   type status = Done of bool
193               | Ready of bool
194
195   let say s = if debug then prerr_endline ("make: "^s);; 
196
197   let unopt_or_call x f y = match x with Some _ -> x | None -> f y;;
198
199   let fst4 = function (x,_,_,_) -> x;;
200
201   let younger_s_t (_,cs, ct, _, _) a b = 
202     let a = try Hashtbl.find cs a with Not_found -> assert false in
203     let b = 
204       try
205         match Hashtbl.find ct b with
206         | Some _ as x -> x
207         | None ->
208            match F.mtime_of_target_object b with
209            | Some t as x -> 
210                Hashtbl.remove ct b;
211                Hashtbl.add ct b x; x
212            | x -> x
213       with Not_found -> assert false
214     in
215     match a, b with 
216     | Some a, Some b -> a < b
217     | _ -> false
218   ;;
219
220   let younger_t_t (_,_,ct, _, _) a b = 
221     let a = 
222       try
223         match Hashtbl.find ct a with
224         | Some _ as x -> x
225         | None ->
226            match F.mtime_of_target_object a with
227            | Some t as x -> 
228                Hashtbl.remove ct b;
229                Hashtbl.add ct a x; x
230            | x -> x
231       with Not_found -> assert false
232     in
233     let b = 
234       try
235         match Hashtbl.find ct b with
236         | Some _ as x -> x
237         | None ->
238            match F.mtime_of_target_object b with
239            | Some t as x -> 
240                Hashtbl.remove ct b;
241                Hashtbl.add ct b x; x
242            | x -> x
243       with Not_found -> assert false
244     in
245     match a, b with
246     | Some a, Some b -> a < b
247     | _ -> false
248   ;;
249
250   let rec purge_unwanted_roots wanted deps =
251     let roots, rest = 
252        List.partition 
253          (fun (t,d,_,_) ->
254            not (List.exists (fun (_,d1,_,_) -> List.mem t d1) deps))
255          deps
256     in
257     let newroots = List.filter (fun (t,_,_,_) -> List.mem t wanted) roots in
258     if newroots = roots then
259       deps
260     else
261       purge_unwanted_roots wanted (newroots @ rest)
262   ;;
263
264   let is_not_ro (opts,_,_,_,_) (f,_,r,_) =
265     match r with
266     | Some root -> not (F.is_readonly_buri_of opts f)
267     | None -> assert false
268   ;;
269
270   let rec get_status opts what =
271      let _, _, _, cc, cd = opts in
272      let t, dependencies, root, tgt = what in
273      try Done (Hashtbl.find cc t)
274 (* say "already built" *)
275      with Not_found ->
276         let map st d = match st with
277            | Done false  -> st
278            | Ready false -> st
279            | _           ->
280               let whatd = Hashtbl.find cd d in
281               let _, _, _, tgtd = whatd in
282               begin match st, get_status opts whatd with
283                  | _, Done false         -> Hashtbl.add cc t false; Done false
284                  | Done true, Done true  -> 
285                     if younger_t_t opts tgt tgtd then Ready true else Done true  
286 (* say (F.string_of_source_object t^" depends on "^F.string_of_target_object unsat^" and "^F.string_of_source_object t^".o is younger than "^ F.string_of_target_object unsat^", thus needs to be built") *)
287                  | Done true, Ready _    -> Ready false
288                  | Ready true, Ready _   -> Ready false
289 (* say (F.string_of_source_object t^" depends on "^ F.string_of_source_object (fst4 unsat)^ " that is not built, thus is not ready") *)
290                  | Ready true, Done true -> Ready true
291                  | _                     -> st
292               end
293         in
294         let st = if younger_s_t opts t tgt then Done true else Ready true in
295         match List.fold_left map st dependencies with
296            | Done true -> Hashtbl.add cc t true; Done true
297 (* say(F.string_of_source_object t^" is built" *)
298            | st     -> st
299
300   let list_partition_filter_rev filter l =
301      let rec aux l1 l2 = function
302         | []       -> l1, l2
303         | hd :: tl ->
304            begin match filter hd with
305               | None       -> aux l1 l2 tl
306               | Some true  -> aux (hd :: l1) l2 tl
307               | Some false -> aux l1 (hd :: l2) tl
308            end
309      in
310      aux [] [] l
311
312   let rec make_aux root (lo,_,ct, cc, _ as opts) ok deps = 
313     timestamp "filter get_status: begin";
314     let map what = match get_status opts what with
315        | Done _  -> None
316        | Ready b -> Some b
317     in
318     let todo, deps = list_partition_filter_rev map deps in
319     timestamp "filter get_status: end";
320     let todo =
321       let local, remote =
322         List.partition (fun (_,_,froot,_) -> froot = Some root) todo
323       in
324       let local, skipped = List.partition (is_not_ro opts) local in
325       List.iter 
326        (fun x -> 
327         HLog.warn("Read only baseuri for: "^F.string_of_source_object(fst4 x)))
328        skipped;
329       remote @ local
330     in
331     if todo <> [] then begin
332        let ok = List.fold_left  
333           (fun ok (file,_,froot,tgt) ->
334             let rc = 
335               match froot with
336               | Some froot when froot = root -> 
337                   Hashtbl.remove ct tgt;
338                   Hashtbl.add ct tgt None;
339                   timestamp "building";
340                   let r = F.build lo file in
341                   timestamp "done"; r
342               | Some froot -> make froot [file]
343               | None -> 
344                   HLog.error ("No root for: "^F.string_of_source_object file);
345                   false
346             in
347             Hashtbl.add cc file rc;
348             ok && rc 
349           )
350           ok (List.rev todo)
351        in
352       make_aux root opts ok (List.rev deps)
353     end
354     else
355       ok
356
357   and  make root targets = 
358     timestamp "entering";
359     HLog.debug ("Entering directory '"^root^"'");
360     let old_root = Sys.getcwd () in
361     Sys.chdir root;
362     let deps = F.load_deps_file (root^"/depends") in
363     let local_options = load_root_file (root^"/root") in
364     let caches,cachet,cachec,cached = 
365        Hashtbl.create 73, Hashtbl.create 73, Hashtbl.create 73, Hashtbl.create 73
366     in
367     (* deps are enriched with these informations to sped up things later *)
368     let deps = 
369       List.map 
370         (fun (file,d) -> 
371           let r,tgt = F.root_and_target_of local_options file in
372           Hashtbl.add caches file (F.mtime_of_source_object file);
373           Hashtbl.add cachet tgt (F.mtime_of_target_object tgt); 
374           Hashtbl.add cached file (file, d, r, tgt);
375           (file, d, r, tgt)
376         )
377         deps
378     in
379     let opts = local_options, caches, cachet, cachec, cached in
380     let ok =
381       if targets = [] then 
382         make_aux root opts true deps
383       else
384         make_aux root opts true 
385           (purge_unwanted_roots targets deps)
386     in
387     HLog.debug ("Leaving directory '"^root^"'");
388     Sys.chdir old_root;
389     timestamp "leaving";
390     ok
391   ;;
392
393 end
394   
395 let write_deps_file where deps = match where with 
396    | Some root ->
397       let oc = open_out (root ^ "/depends") in
398       let map (t, d) = output_string oc (t^" "^String.concat " " d^"\n") in
399       List.iter map deps; close_out oc;
400       HLog.message ("Generated: " ^ root ^ "/depends")
401    | None -> 
402       print_endline (String.concat " " (List.flatten (List.map snd deps)))
403       
404 (* FG ***********************************************************************)
405
406 (* scheme uri part as defined in URI Generic Syntax (RFC 3986) *)
407 let uri_scheme_rex = Pcre.regexp "^[[:alpha:]][[:alnum:]\-+.]*:"
408
409 let is_uri str =
410    Pcre.pmatch ~rex:uri_scheme_rex str