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 refresh_uri uri = NUri.uri_of_string (NUri.string_of_uri uri);;
21 let refresh_uri_in_universe =
22 List.map (fun (x,u) -> x, refresh_uri u)
25 let refresh_uri_in_reference (NReference.Ref (uri,spec)) =
26 NReference.reference_of_spec (refresh_uri uri) spec
28 let refresh_uri_in_term status =
31 | NCic.Meta (i,(n,NCic.Ctx l)) ->
32 NCic.Meta (i,(n,NCic.Ctx (List.map aux l)))
33 | NCic.Meta _ as t -> t
34 | NCic.Const ref -> NCic.Const (refresh_uri_in_reference ref)
35 | NCic.Sort (NCic.Type l) -> NCic.Sort (NCic.Type (refresh_uri_in_universe l))
36 | NCic.Match (NReference.Ref (uri,spec),outtype,term,pl) ->
37 let r = NReference.reference_of_spec (refresh_uri uri) spec in
38 let outtype = aux outtype in
39 let term = aux term in
40 let pl = List.map aux pl in
41 NCic.Match (r,outtype,term,pl)
42 | t -> NCicUtils.map status (fun _ _ -> ()) () (fun _ -> aux) t
47 let refresh_uri_in_obj status (uri,height,metasenv,subst,obj_kind) =
48 assert (metasenv = []);
50 refresh_uri uri,height,metasenv,subst,
51 NCicUntrusted.map_obj_kind (refresh_uri_in_term status) obj_kind
54 let ng_path_of_baseuri ?(no_suffix=false) baseuri =
55 let uri = NUri.string_of_uri baseuri in
56 let path = String.sub uri 4 (String.length uri - 4) in
57 let path = Helm_registry.get "matita.basedir" ^ path in
58 let dirname = Filename.dirname path in
59 HExtlib.mkdir dirname;
66 let require_path path =
67 let ch = open_in path in
68 let mmagic,dump = Marshal.from_channel ch in
70 if mmagic <> magic then
71 raise (LibraryOutOfSync (lazy "The library is out of sync with the implementation. Please recompile the library."))
76 let require0 ~baseuri = require_path (ng_path_of_baseuri baseuri)
78 let db_path () = Helm_registry.get "matita.basedir" ^ "/ng_db.ng";;
81 [ `Obj of NUri.uri * NCic.obj
82 | `Constr of NCic.universe * NCic.universe] list *
83 (NUri.uri * string * NReference.reference) list
87 let storage = ref [];;
88 let local_aliases = ref [];;
90 let load_db,set_global_aliases,get_global_aliases,add_deps,get_deps,remove_deps=
91 let global_aliases = ref [] in
92 let rev_includes_map = ref NUri.UriMap.empty in
94 let ch = open_out (db_path ()) in
95 Marshal.to_channel ch (magic,(!global_aliases,!rev_includes_map)) [];
98 HExtlib.mkdir (Helm_registry.get "matita.basedir");
100 let ga,im = require_path (db_path ()) in
103 (fun (uri,name,NReference.Ref (uri2,spec)) ->
104 refresh_uri uri,name,NReference.reference_of_spec (refresh_uri uri2) spec
108 (fun u l im -> NUri.UriMap.add (refresh_uri u) (List.map refresh_uri l) im
109 ) im NUri.UriMap.empty
111 global_aliases := ga;
112 rev_includes_map := im
116 let get_deps_one_step u =
117 try NUri.UriMap.find u !rev_includes_map with Not_found -> [] in
122 if List.mem he res then
125 aux (he::res) (get_deps_one_step he @ tl)
129 rev_includes_map := NUri.UriMap.remove u !rev_includes_map;
132 (fun l -> List.filter (fun uri -> not (NUri.eq u uri)) l) !rev_includes_map;
136 (fun ga -> global_aliases := ga; store_db ()),
137 (fun () -> !global_aliases),
139 rev_includes_map := NUri.UriMap.add u (l @ get_deps u) !rev_includes_map;
147 class virtual status =
150 val timestamp = (time0 : timestamp)
151 method timestamp = timestamp
152 method set_timestamp v = {< timestamp = v >}
155 let time_travel0 (sto,ali) =
156 let diff_len = List.length !storage - List.length sto in
157 let to_be_deleted,_ = HExtlib.split_nth diff_len !storage in
158 if List.length to_be_deleted > 0 then
159 List.iter NCicEnvironment.invalidate_item to_be_deleted;
160 storage := sto; local_aliases := ali
163 let time_travel status = time_travel0 status#timestamp;;
165 type obj = string * Obj.t
166 (* includes are transitively closed; dependencies are only immediate *)
168 { objs: obj list ; includes: NUri.uri list; dependencies: string list }
170 class type g_dumpable_status =
175 class dumpable_status =
177 val db = { objs = []; includes = []; dependencies = [] }
179 method set_dump v = {< db = v >}
180 method set_dumpable_status
181 : 'status. #g_dumpable_status as 'status -> 'self
182 = fun o -> {< db = o#dump >}
185 let get_transitively_included status =
189 let dump_obj status obj =
190 status#set_dump {status#dump with objs = obj::status#dump.objs }
193 module type SerializerType =
197 type 'a register_type =
199 refresh_uri_in_universe:(NCic.universe -> NCic.universe) ->
200 refresh_uri_in_term:(NCic.status -> NCic.term -> NCic.term) ->
201 refresh_uri_in_reference:(NReference.reference -> NReference.reference) ->
203 dumpable_status -> dumpable_status
205 val register: < run: 'a. string -> 'a register_type -> ('a -> obj) >
206 val serialize: baseuri:NUri.uri -> dumpable_status -> unit
208 baseuri:NUri.uri -> fname:string -> alias_only:bool ->
209 dumpable_status -> dumpable_status
210 val dependencies_of: baseuri:NUri.uri -> string list
213 module Serializer(D: sig type dumpable_s val get: dumpable_s -> dumpable_status val set: dumpable_s -> dumpable_status -> dumpable_s end) =
215 type dumpable_status = D.dumpable_s
216 type 'a register_type =
218 refresh_uri_in_universe:(NCic.universe -> NCic.universe) ->
219 refresh_uri_in_term:(NCic.status -> NCic.term -> NCic.term) ->
220 refresh_uri_in_reference:(NReference.reference -> NReference.reference) ->
222 dumpable_status -> dumpable_status
224 let require1 = ref (fun ~alias_only:_ _ -> assert false) (* unknown data*)
225 let already_registered = ref []
229 method run : 'a. string -> 'a register_type -> ('a -> obj)
231 assert (not (List.mem tag !already_registered));
232 already_registered := tag :: !already_registered;
233 let old_require1 = !require1 in
235 (fun ~alias_only ((tag',data) as x) ->
237 require (Obj.magic data) ~refresh_uri_in_universe ~refresh_uri_in_term
238 ~refresh_uri_in_reference ~alias_only
240 old_require1 ~alias_only x);
241 (fun x -> tag,Obj.repr x)
244 let serialize ~baseuri status =
245 let status = D.get status in
246 let ch = open_out (ng_path_of_baseuri baseuri) in
247 Marshal.to_channel ch (magic,(status#dump.dependencies,status#dump.objs)) [];
252 let ch = open_out (ng_path_of_baseuri uri) in
253 Marshal.to_channel ch (magic,obj) [];
257 set_global_aliases (!local_aliases @ get_global_aliases ());
258 List.iter (fun u -> add_deps u [baseuri]) status#dump.includes;
261 let require2 ~baseuri ~alias_only status =
263 let s = D.get status in
268 includes = baseuri::List.filter ((<>) baseuri) s#dump.includes}) in
269 let _dependencies,dump = require0 ~baseuri in
270 List.fold_right (!require1 ~alias_only) dump status
273 raise (IncludedFileNotCompiled(ng_path_of_baseuri baseuri,NUri.string_of_uri baseuri))
275 let dependencies_of ~baseuri = fst (require0 ~baseuri)
278 let aux (baseuri,fname) ~refresh_uri_in_universe:_ ~refresh_uri_in_term:_
279 ~refresh_uri_in_reference:_ ~alias_only status =
281 alias_only || List.mem baseuri (get_transitively_included (D.get status))
283 HLog.warn ("include " ^ (if alias_only then "alias " else "") ^ fname);
284 let status = require2 ~baseuri ~alias_only status in
285 HLog.warn ("done: include " ^ (if alias_only then "alias " else "") ^ fname);
288 register#run "include" aux
290 let require ~baseuri ~fname ~alias_only status =
292 alias_only || List.mem baseuri (get_transitively_included (D.get status)) in
294 if not alias_only then
295 let s = D.get status in
299 includes = baseuri::s#dump.includes;
300 dependencies = fname::s#dump.dependencies})
303 let status = require2 ~baseuri ~alias_only status in
304 let s = D.get status in
308 objs = record_include (baseuri,fname)::s#dump.objs })
311 let fetch_obj status uri =
312 let obj = require0 ~baseuri:uri in
313 refresh_uri_in_obj status obj
319 (fun (_,name',nref) -> if name'=name then Some nref else None)
320 (!local_aliases @ get_global_aliases ())
322 Not_found -> raise (NCicEnvironment.ObjectNotFound (lazy name))
327 (fun (uri',_,nref) ->
328 if NUri.eq uri' uri then Some nref else None) !local_aliases
331 let add_obj status ((u,_,_,_,_) as obj) =
332 NCicEnvironment.check_and_add_obj status obj;
333 storage := (`Obj (u,obj))::!storage;
334 let _,height,_,_,obj = obj in
337 NCic.Constant (_,name,None,_,_) ->
338 [u,name,NReference.reference_of_spec u NReference.Decl]
339 | NCic.Constant (_,name,Some _,_,_) ->
340 [u,name,NReference.reference_of_spec u (NReference.Def height)]
341 | NCic.Fixpoint (is_ind,fl,_) ->
343 (fun (_,name,recno,_,_) i ->
345 u,name,NReference.reference_of_spec u(NReference.Fix(i,recno,height))
347 u,name,NReference.reference_of_spec u (NReference.CoFix i)) fl
348 | NCic.Inductive (inductive,leftno,il,_) ->
351 (fun (_,iname,_,cl) i ->
355 NReference.reference_of_spec u (NReference.Con (i,j+1,leftno))
358 NReference.reference_of_spec u
359 (NReference.Ind (inductive,i,leftno))]
362 local_aliases := references @ !local_aliases;
363 status#set_timestamp (!storage,!local_aliases)
366 let add_constraint status u1 u2 =
369 (function `Constr (u1',u2') when u1=u1' && u2=u2' -> true | _ -> false)
372 (*CSC: raise an exception here! *)
373 (prerr_endline "CANNOT ADD A CONSTRAINT TWICE"; assert false);
374 NCicEnvironment.add_lt_constraint u1 u2;
375 storage := (`Constr (u1,u2)) :: !storage;
376 status#set_timestamp (!storage,!local_aliases)
379 let get_obj status u =
383 (function `Obj (u,o) -> Some (u,o) | _ -> None )
386 try fetch_obj status u
388 raise (NCicEnvironment.ObjectNotFound (lazy (NUri.string_of_uri u)))
391 NCicEnvironment.set_get_obj get_obj;;