2 ||M|| This file is part of HELM, an Hypertextual, Electronic
3 ||A|| Library of Mathematics, developed at the Computer Science
4 ||T|| Department, University of Bologna, Italy.
6 ||T|| HELM is free software; you can redistribute it and/or
7 ||A|| modify it under the terms of the GNU General Public License
8 \ / version 2 or (at your option) any later version.
9 \ / This software is distributed as is, NO WARRANTY.
10 V_______________________________________________________________ *)
14 exception LibraryOutOfSync of string Lazy.t
15 exception IncludedFileNotCompiled of string * string
19 let prerr_endline _ = ()
21 let refresh_uri uri = NUri.uri_of_string (NUri.string_of_uri uri);;
23 let refresh_uri_in_universe =
24 List.map (fun (x,u) -> x, refresh_uri u)
27 let refresh_uri_in_reference (NReference.Ref (uri,spec)) =
28 NReference.reference_of_spec (refresh_uri uri) spec
30 let refresh_uri_in_term status =
33 | NCic.Meta (i,(n,NCic.Ctx l)) ->
34 NCic.Meta (i,(n,NCic.Ctx (List.map aux l)))
35 | NCic.Meta _ as t -> t
36 | NCic.Const ref -> NCic.Const (refresh_uri_in_reference ref)
37 | NCic.Sort (NCic.Type l) -> NCic.Sort (NCic.Type (refresh_uri_in_universe l))
38 | NCic.Match (NReference.Ref (uri,spec),outtype,term,pl) ->
39 let r = NReference.reference_of_spec (refresh_uri uri) spec in
40 let outtype = aux outtype in
41 let term = aux term in
42 let pl = List.map aux pl in
43 NCic.Match (r,outtype,term,pl)
44 | t -> NCicUtils.map status (fun _ _ -> ()) () (fun _ -> aux) t
49 let refresh_uri_in_obj status (uri,height,metasenv,subst,obj_kind) =
50 assert (metasenv = []);
52 refresh_uri uri,height,metasenv,subst,
53 NCicUntrusted.map_obj_kind (refresh_uri_in_term status) obj_kind
56 let ng_path_of_baseuri ?(no_suffix=false) user baseuri =
57 let uri = NUri.string_of_uri baseuri in
58 let path = String.sub uri 4 (String.length uri - 4) in
59 let path = match user with
60 | Some u -> "/" ^ u ^ path
61 | _ -> prerr_endline "WARNING: ng_path_of_baseuri called without a uid"; path
63 let path = Helm_registry.get "matita.basedir" ^ path in
64 let dirname = Filename.dirname path in
65 HExtlib.mkdir dirname;
72 let require_path path =
73 let ch = open_in path in
74 let mmagic,dump = Marshal.from_channel ch in
76 if mmagic <> magic then
77 raise (LibraryOutOfSync (lazy "The library is out of sync with the implementation. Please recompile the library."))
82 let require0 user ~baseuri = require_path (ng_path_of_baseuri user baseuri)
85 let midpath = match user with
89 Helm_registry.get "matita.basedir" ^ midpath ^ "/ng_db.ng";;
92 [ `Obj of NUri.uri * NCic.obj
93 | `Constr of NCic.universe * NCic.universe] list *
94 (NUri.uri * string * NReference.reference) list
99 let global_aliases_db = ref [];;
100 let rev_includes_map_db = ref [];;
102 let global_aliases u =
103 try List.assoc u !global_aliases_db
106 global_aliases_db := (u,db)::!global_aliases_db;
110 let rev_includes_map u =
111 try List.assoc u !rev_includes_map_db
113 let db = ref NUri.UriMap.empty in
114 rev_includes_map_db := (u,db)::!rev_includes_map_db;
118 let load_db,set_global_aliases,get_global_aliases,add_deps,get_deps,remove_deps=
120 let ch = open_out (db_path user) in
121 Marshal.to_channel ch (magic,(!(global_aliases user),!(rev_includes_map user))) [];
124 HExtlib.mkdir (Helm_registry.get "matita.basedir");
125 if user <> None then HExtlib.mkdir ((Helm_registry.get "matita.basedir") ^ "/" ^ HExtlib.unopt user);
127 let ga,im = require_path (db_path user) in
130 (fun (uri,name,NReference.Ref (uri2,spec)) ->
131 refresh_uri uri,name,NReference.reference_of_spec (refresh_uri uri2) spec
135 (fun u l im -> NUri.UriMap.add (refresh_uri u) (List.map refresh_uri l) im
136 ) im NUri.UriMap.empty
138 global_aliases user := ga;
139 rev_includes_map user := im
142 let get_deps user u =
143 let get_deps_one_step u =
144 try NUri.UriMap.find u !(rev_includes_map user) with Not_found -> [] in
149 if List.mem he res then
152 aux (he::res) (get_deps_one_step he @ tl)
155 let remove_deps user u =
156 rev_includes_map user := NUri.UriMap.remove u !(rev_includes_map user);
157 rev_includes_map user :=
159 (fun l -> List.filter (fun uri -> not (NUri.eq u uri)) l) !(rev_includes_map user);
163 (fun user ga -> global_aliases user := ga; store_db user),
164 (fun user -> !(global_aliases user)),
166 rev_includes_map user := NUri.UriMap.add u (l @ get_deps user u) !(rev_includes_map user);
176 [ `Obj of NUri.uri * NCic.obj
177 | `Constr of NCic.universe * NCic.universe] list ref;
179 (NUri.uri * string * NReference.reference) list ref
182 class type g_status =
184 inherit NCicEnvironment.g_status
188 class virtual status uid =
190 inherit NCicEnvironment.status uid
194 local_aliases = ref []
196 method lib_db = lib_db
198 val timestamp = (time0 : timestamp)
199 method timestamp = timestamp
201 method print_timestamp () =
202 prerr_endline ("length(lib_db.storage) = " ^
203 string_of_int (List.length !(lib_db.storage)));
204 prerr_endline ("length(timestamp.storage) = " ^
205 string_of_int (List.length (fst timestamp)));
206 method set_timestamp v = {< timestamp = v >}
207 method set_lib_db v = {< lib_db = v >}
208 method set_lib_status : 's.#g_status as 's -> 'self
209 = fun o -> {< lib_db = o#lib_db >}#set_env_status o
212 let reset_timestamp st =
213 st#lib_db.storage := [];
214 st#lib_db.local_aliases := []
217 let time_travel0 st (sto,ali) =
218 prerr_endline ("length of lib_db.storage = " ^ (string_of_int (List.length !(st#lib_db.storage))));
219 prerr_endline ("length of sto = " ^ (string_of_int (List.length sto)));
220 let diff_len = List.length !(st#lib_db.storage) - List.length sto in
221 let to_be_deleted,_ = HExtlib.split_nth diff_len !(st#lib_db.storage) in
222 if List.length to_be_deleted > 0 then
223 List.iter (NCicEnvironment.invalidate_item st) to_be_deleted;
224 st#lib_db.storage := sto; st#lib_db.local_aliases := ali
227 let time_travel status = time_travel0 status status#timestamp;;
229 type obj = string * Obj.t
230 (* includes are transitively closed; dependencies are only immediate *)
232 { objs: obj list ; includes: NUri.uri list; dependencies: string list }
234 class type g_dumpable_status =
239 (* uid = None --> single user mode *)
240 class dumpable_status uid =
242 inherit NCicPp.status uid
245 val db = { objs = []; includes = []; dependencies = [] }
247 method set_dump v = {< db = v >}
248 method set_dumpable_status
249 : 'status. #g_dumpable_status as 'status -> 'self
250 = fun o -> {< db = o#dump >}
253 let get_transitively_included status =
257 let dump_obj status obj =
258 status#set_dump {status#dump with objs = obj::status#dump.objs }
261 module type SerializerType =
265 type 'a register_type =
267 refresh_uri_in_universe:(NCic.universe -> NCic.universe) ->
268 refresh_uri_in_term:(NCicEnvironment.status -> NCic.term -> NCic.term) ->
269 refresh_uri_in_reference:(NReference.reference -> NReference.reference) ->
271 dumpable_status -> dumpable_status
273 val register: < run: 'a. string -> 'a register_type -> ('a -> obj) >
274 val serialize: baseuri:NUri.uri -> dumpable_status -> unit
276 baseuri:NUri.uri -> fname:string -> alias_only:bool ->
277 dumpable_status -> dumpable_status
278 val dependencies_of: string option -> baseuri:NUri.uri -> string list
281 module Serializer(D: sig type dumpable_s val get: dumpable_s -> dumpable_status
282 val set: dumpable_s -> dumpable_status -> dumpable_s val user : dumpable_s ->
285 type dumpable_status = D.dumpable_s
286 type 'a register_type =
288 refresh_uri_in_universe:(NCic.universe -> NCic.universe) ->
289 refresh_uri_in_term:(NCicEnvironment.status -> NCic.term -> NCic.term) ->
290 refresh_uri_in_reference:(NReference.reference -> NReference.reference) ->
292 dumpable_status -> dumpable_status
294 let require1 = ref (fun ~alias_only:_ _ -> assert false) (* unknown data*)
295 let already_registered = ref []
299 method run : 'a. string -> 'a register_type -> ('a -> obj)
301 assert (not (List.mem tag !already_registered));
302 already_registered := tag :: !already_registered;
303 let old_require1 = !require1 in
304 prerr_endline "let old_require 1 superata";
306 (fun ~alias_only ((tag',data) as x) ->
308 (prerr_endline ("requiring tag': " ^ tag');
309 require (Obj.magic data) ~refresh_uri_in_universe ~refresh_uri_in_term
310 ~refresh_uri_in_reference ~alias_only)
312 old_require1 ~alias_only x);
313 prerr_endline ("added require tag" ^ tag);
314 (fun x -> tag,Obj.repr x)
317 let serialize ~baseuri status =
318 let ch = open_out (ng_path_of_baseuri (D.get status)#user baseuri) in
319 Marshal.to_channel ch (magic,((D.get status)#dump.dependencies,(D.get status)#dump.objs)) [];
321 let deps = String.concat ", " ((D.get status)#dump.dependencies) in
322 prerr_endline ("dumping dependencies:\n" ^ deps ^ "\nend of deps");
326 let ch = open_out (ng_path_of_baseuri (D.get status)#user uri) in
327 Marshal.to_channel ch (magic,obj) [];
330 ) !((D.get status)#lib_db.storage);
331 let user = D.user status in
332 set_global_aliases user (!((D.get status)#lib_db.local_aliases) @ get_global_aliases user);
333 List.iter (fun u -> add_deps (D.user status) u [baseuri]) (D.get status)#dump.includes;
334 reset_timestamp (D.get status)
336 let require2 ~baseuri ~alias_only status =
338 let s = D.get status in
343 includes = baseuri::List.filter ((<>) baseuri) s#dump.includes}) in
344 let _dependencies,dump = require0 (D.get status)#user ~baseuri in
345 List.fold_right (!require1 ~alias_only) dump status
348 raise (IncludedFileNotCompiled(ng_path_of_baseuri (D.get status)#user baseuri,NUri.string_of_uri baseuri))
350 let dependencies_of user ~baseuri = fst (require0 user ~baseuri)
353 let aux (baseuri,fname) ~refresh_uri_in_universe:_ ~refresh_uri_in_term:_
354 ~refresh_uri_in_reference:_ ~alias_only status =
356 alias_only || List.mem baseuri (get_transitively_included (D.get status))
358 HLog.warn ("include " ^ (if alias_only then "alias " else "") ^ fname);
359 let status = require2 ~baseuri ~alias_only status in
360 HLog.warn ("done: include " ^ (if alias_only then "alias " else "") ^ fname);
363 register#run "include" aux
365 let require ~baseuri ~fname ~alias_only status =
367 alias_only || List.mem baseuri (get_transitively_included (D.get status)) in
369 if not alias_only then
370 let s = D.get status in
374 includes = baseuri::s#dump.includes;
375 dependencies = fname::s#dump.dependencies})
378 let status = require2 ~baseuri ~alias_only status in
379 let s = D.get status in
383 objs = record_include (baseuri,fname)::s#dump.objs })
386 let fetch_obj user status uri =
387 let obj = require0 user ~baseuri:uri in
388 refresh_uri_in_obj status obj
391 let resolve st name =
394 (fun (_,name',nref) -> if name'=name then Some nref else None)
395 (!(st#lib_db.local_aliases) @ get_global_aliases st#user)
398 (prerr_endline ("can't resolve object " ^ name);
399 raise (NCicEnvironment.ObjectNotFound (lazy name)))
402 let aliases_of st uri =
404 (fun (uri',_,nref) ->
405 if NUri.eq uri' uri then Some nref else None) !(st#lib_db.local_aliases)
408 let add_obj status ((u,_,_,_,_) as obj) =
409 NCicEnvironment.check_and_add_obj status obj;
410 status#lib_db.storage := (`Obj (u,obj))::!(status#lib_db.storage);
411 let _,height,_,_,obj = obj in
414 NCic.Constant (_,name,None,_,_) ->
415 [u,name,NReference.reference_of_spec u NReference.Decl]
416 | NCic.Constant (_,name,Some _,_,_) ->
417 [u,name,NReference.reference_of_spec u (NReference.Def height)]
418 | NCic.Fixpoint (is_ind,fl,_) ->
420 (fun (_,name,recno,_,_) i ->
422 u,name,NReference.reference_of_spec u(NReference.Fix(i,recno,height))
424 u,name,NReference.reference_of_spec u (NReference.CoFix i)) fl
425 | NCic.Inductive (inductive,leftno,il,_) ->
428 (fun (_,iname,_,cl) i ->
432 NReference.reference_of_spec u (NReference.Con (i,j+1,leftno))
435 NReference.reference_of_spec u
436 (NReference.Ind (inductive,i,leftno))]
439 status#lib_db.local_aliases := references @ !(status#lib_db.local_aliases);
440 status#set_timestamp (!(status#lib_db.storage),!(status#lib_db.local_aliases))
443 let add_constraint status u1 u2 =
446 (function `Constr (u1',u2') when u1=u1' && u2=u2' -> true | _ -> false)
447 !(status#lib_db.storage)
449 (*CSC: raise an exception here! *)
450 (prerr_endline "CANNOT ADD A CONSTRAINT TWICE"; assert false);
451 NCicEnvironment.add_lt_constraint status u1 u2;
452 status#lib_db.storage := (`Constr (u1,u2)) :: !(status#lib_db.storage);
453 status#set_timestamp (!(status#lib_db.storage),!(status#lib_db.local_aliases))
456 let get_obj status u =
461 (function `Obj (u,o) -> Some (u,o) | _ -> None )
462 !(status#lib_db.storage))
464 try fetch_obj (status#user) status u
466 (prerr_endline ("can't fetch object " ^ NUri.string_of_uri u);
467 raise (NCicEnvironment.ObjectNotFound (lazy (NUri.string_of_uri u))))
470 NCicEnvironment.set_get_obj
471 (get_obj :> NCicEnvironment.status -> NUri.uri -> NCic.obj);;