]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/registry/helm_registry.ml
- no longer needs PXP
[helm.git] / helm / ocaml / registry / helm_registry.ml
1 (* Copyright (C) 2004, 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 open Printf
27
28 let debug = false
29 let debug_print s =
30   if debug then prerr_endline ("Helm_registry debugging: " ^ s)
31
32   (** <helpers> *)
33
34 let list_uniq l =
35   let rec aux last_element = function
36     | [] -> []
37     | hd :: tl ->
38         (match last_element with
39         | Some elt when elt = hd -> aux last_element tl
40         | _ -> hd :: aux (Some hd) tl)
41   in
42   aux None l
43
44 let starts_with prefix =
45 (*
46   let rex = Str.regexp (Str.quote prefix) in
47   fun s -> Str.string_match rex s 0
48 *)
49   let prefix_len = String.length prefix in
50   fun s ->
51     try
52       String.sub s 0 prefix_len = prefix
53     with Invalid_argument _ -> false
54
55 let hashtbl_keys tbl = Hashtbl.fold (fun k _ acc -> k :: acc) tbl []
56 let hashtbl_pairs tbl = Hashtbl.fold (fun k v acc -> (k,v) :: acc) tbl []
57
58   (** </helpers> *)
59
60 exception Malformed_key of string
61 exception Key_not_found of string
62 exception Cyclic_definition of string
63 exception Type_error of string * string * string (* expected type, value, msg *)
64 exception Parse_error of string * int * int * string  (* file, line, col, msg *)
65 exception Invalid_value of (string * string) * string (* key, value, descr *)
66
67 (*
68 type validator_id = int
69
70 let get_next_validator_id =
71   let next_id = ref 0 in
72   fun () ->
73     incr next_id;
74     !next_id
75
76 let validators = Hashtbl.create magic_size
77 *)
78
79   (* root XML tag: used by save_to, ignored by load_from *)
80 let root_tag = "helm_registry"
81
82 let magic_size = 127
83
84 let backup_registry registry = Hashtbl.copy registry
85 let restore_registry backup registry =
86   Hashtbl.clear registry;
87   Hashtbl.iter (fun key value -> Hashtbl.replace registry key value) backup
88
89   (* as \\w but:
90    * - no sequences of '_' longer than 1 are permitted
91    *)
92 let valid_step_rex_raw = "[a-zA-Z0-9]+\\(_[a-z0A-Z-9]+\\)*"
93 let valid_key_rex_raw =
94   sprintf "%s\\(\\.%s\\)*" valid_step_rex_raw valid_step_rex_raw
95 let valid_key_rex = Str.regexp ("^" ^ valid_key_rex_raw ^ "$")
96 let interpolated_key_rex = Str.regexp ("\\$(" ^ valid_key_rex_raw ^ ")")
97 let dot_rex = Str.regexp "\\."
98 let spaces_rex = Str.regexp "[ \t\n\r]+"
99 let heading_spaces_rex = Str.regexp "^[ \t\n\r]+"
100 let margin_blanks_rex =
101   Str.regexp "^\\([ \t\n\r]*\\)\\([^ \t\n\r]*\\)\\([ \t\n\r]*\\)$"
102
103 let strip_blanks s = Str.global_replace margin_blanks_rex "\\2" s
104
105 let split s =
106   (* trailing blanks are removed per default by split *)
107   Str.split spaces_rex (Str.global_replace heading_spaces_rex "" s)
108 let merge l = String.concat " " l
109
110   (* escapes for xml configuration file *)
111 let (escape, unescape) =
112   let (in_enc, out_enc) = (`Enc_utf8, `Enc_utf8) in
113   (Netencoding.Html.encode ~in_enc ~out_enc (),
114    Netencoding.Html.decode ~in_enc ~out_enc ~entity_base:`Xml ())
115
116 let key_is_valid key =
117   if not (Str.string_match valid_key_rex key 0) then
118     raise (Malformed_key key)
119
120 (*
121 let value_is_valid ~key ~value =
122   List.iter
123     (fun (validator, descr) ->
124       if not (validator value) then
125         raise (Invalid_value ((key, value), descr)))
126     (Hashtbl.find_all validators key)
127 *)
128
129 let set' registry ~key ~value =
130   debug_print (sprintf "Setting %s = %s" key value);
131   key_is_valid key;
132 (*   value_is_valid ~key ~value; *)
133   Hashtbl.replace registry key value
134
135 let unset registry = Hashtbl.remove registry
136
137 let env_var_of_key = Str.global_replace dot_rex "__"
138
139 let get registry key =
140   let rec aux stack key =
141     key_is_valid key;
142     if List.mem key stack then begin
143       let msg = (String.concat " -> " (List.rev stack)) ^ " -> " ^ key in
144       raise (Cyclic_definition msg)
145     end;
146     let registry_value =  (* internal value *)
147       try
148         Some (Hashtbl.find registry key)
149       with Not_found -> None
150     in
151     let env_value = (* environment value *)
152       try
153         Some (Sys.getenv (env_var_of_key key))
154       with Not_found -> None
155     in
156     let value = (* resulting value *)
157       match (registry_value, env_value) with
158       | Some reg, Some env  -> env
159       | Some reg, None      -> reg
160       | None,     Some env  -> env
161       | None,     None      -> raise (Key_not_found key)
162     in
163     interpolate (key :: stack) value
164   and interpolate stack value =
165     Str.global_substitute interpolated_key_rex
166       (fun s ->
167         let matched = Str.matched_string s in
168           (* "$(var)" -> "var" *)
169         let key = String.sub matched 2 (String.length matched - 3) in
170         aux stack key)
171       value
172   in
173   strip_blanks (aux [] key)
174
175 let set registry = set' registry
176
177 let has registry key = Hashtbl.mem registry key
178
179 let mk_get_set type_name
180   (from_string: string -> 'a) (to_string: 'a -> string)
181   =
182   let getter registry key =
183     let value = get registry key in
184     try
185       from_string value
186     with exn ->
187       raise (Type_error (type_name, value, Printexc.to_string exn))
188   in
189   let setter registry ~key ~value =
190     set registry ~key ~value:(to_string value)
191   in
192   (getter, setter)
193
194 let (get_string, set_string) = (get, set)
195 let (get_int, set_int) = mk_get_set "int" int_of_string string_of_int
196 let (get_float, set_float) = mk_get_set "float" float_of_string string_of_float
197 let (get_bool, set_bool) = mk_get_set "bool" bool_of_string string_of_bool
198 let (get_string_list, set_string_list) = mk_get_set "string list" split merge
199
200 let get_opt registry getter key =
201   try
202     Some (getter registry key)
203   with Key_not_found _ -> None
204 let set_opt registry setter ~key ~value =
205   match value with
206   | None -> unset registry key
207   | Some value -> setter registry ~key ~value
208 let get_opt_default registry getter default key =
209   match get_opt registry getter key with
210   | None -> default
211   | Some v -> v
212
213 (*
214 let add_validator ~key ~validator ~descr =
215   let id = get_next_validator_id () in
216   Hashtbl.add validators key (validator, descr);
217   id
218 *)
219
220 type xml_tree =
221   | Cdata of string
222   | Element of string * (string * string) list * xml_tree list
223
224 let dot_RE = Str.regexp "\\."
225
226 let xml_tree_of_registry registry =
227   let has_child name elements =
228     List.exists
229       (function
230         | Element (_, ["name", name'], _) when name = name' -> true
231         | _ -> false)
232       elements
233   in
234   let rec get_child name = function
235     | [] -> assert false
236     | (Element (_, ["name", name'], _) as child) :: tl when name = name' ->
237         child, tl
238     | hd :: tl ->
239         let child, rest = get_child name tl in
240         child, hd :: rest
241   in
242   let rec add_key path value tree =
243     match path, tree with
244     | [key], Element (name, attrs, children) ->
245         Element (name, attrs,
246           Element ("key", ["name", key],
247             [Cdata (strip_blanks value)]) :: children)
248     | dir :: path, Element (name, attrs, children) ->
249         if has_child dir children then
250           let child, rest = get_child dir children in
251           Element (name, attrs, add_key path value child :: rest)
252         else
253           Element (name, attrs,
254             ((add_key path value (Element ("section", ["name", dir], [])))
255               :: children))
256     | _ -> assert false
257   in
258   Hashtbl.fold
259     (fun k v tree -> add_key ("helm_registry" :: (Str.split dot_RE k)) v tree)
260     registry
261     (Element ("helm_registry", [], []))
262
263 let rec stream_of_xml_tree = function
264   | Cdata s -> Xml.xml_cdata s
265   | Element (name, attrs, children) ->
266       Xml.xml_nempty name
267         (List.map (fun (n, v) -> (None, n, v)) attrs)
268         (stream_of_xml_trees children)
269 and stream_of_xml_trees = function
270   | [] -> [< >]
271   | hd :: tl -> [< stream_of_xml_tree hd; stream_of_xml_trees tl >]
272
273 let save_to registry fname =
274   let token_stream = stream_of_xml_tree (xml_tree_of_registry registry) in
275   let oc = open_out fname in
276   Xml.pp_to_outchan token_stream oc;
277   close_out oc
278
279 (* PXP version *)
280 (*open Pxp_dtd*)
281 (*open Pxp_document*)
282 (*open Pxp_types*)
283 (*open Pxp_yacc*)
284
285 (*let save_to =*)
286 (*  let dtd = new dtd PxpHelmConf.pxp_config.warner `Enc_utf8 in*)
287 (*  let create_key_node key value = |+ create a <key name="foo">value</key> +|*)
288 (*    let element =*)
289 (*      create_element_node ~valcheck:false PxpHelmConf.pxp_spec dtd*)
290 (*        "key" ["name", key]*)
291 (*    in*)
292 (*    let data = create_data_node PxpHelmConf.pxp_spec dtd value in*)
293 (*    element#append_node data;*)
294 (*    element*)
295 (*  in*)
296 (*  let is_section name =*)
297 (*    fun node ->*)
298 (*      match node#node_type with*)
299 (*      | T_element "section" ->*)
300 (*          (try node#attribute "name" = Value name with Not_found -> false)*)
301 (*      | _ -> false*)
302 (*  in*)
303 (*  let add_key_node root sections key value =*)
304 (*    let rec aux node = function*)
305 (*      | [] ->*)
306 (*          let key_node = create_key_node key value in*)
307 (*          node#append_node key_node*)
308 (*      | section :: tl ->*)
309 (*          let next_node =*)
310 (*            try*)
311 (*              find ~deeply:false (is_section section) node*)
312 (*            with Not_found ->*)
313 (*              let section_node =*)
314 (*                create_element_node ~valcheck:false PxpHelmConf.pxp_spec dtd*)
315 (*                  "section" ["name", section]*)
316 (*              in*)
317 (*              node#append_node section_node;*)
318 (*              section_node*)
319 (*          in*)
320 (*          aux next_node tl*)
321 (*    in*)
322 (*    aux root sections*)
323 (*  in*)
324 (*  fun registry fname ->*)
325 (*    let xml_root =*)
326 (*      create_element_node ~valcheck:false PxpHelmConf.pxp_spec dtd*)
327 (*      "helm_registry" []*)
328 (*    in*)
329 (*    Hashtbl.iter*)
330 (*      (fun key value ->*)
331 (*        let sections, key =*)
332 (*          let hd, tl =*)
333 (*            match List.rev (Str.split dot_RE key) with*)
334 (*            | hd :: tl -> hd, tl*)
335 (*            | _ -> assert false*)
336 (*          in*)
337 (*          List.rev tl, hd*)
338 (*        in*)
339 (*        add_key_node xml_root sections key value)*)
340 (*      registry;*)
341 (*      let outfile = open_out fname in*)
342 (*      Unix.lockf (Unix.descr_of_out_channel outfile) Unix.F_LOCK 0; |+ blocks +|*)
343 (*      if*)
344 (*        Unix.system "xmllint --version &> /dev/null" = Unix.WEXITED 0*)
345 (*      then begin*)
346 (*        let (xmllint_in, xmllint_out) =*)
347 (*          Unix.open_process "xmllint --format --encode utf8 -"*)
348 (*        in*)
349 (*        xml_root#write (`Out_channel xmllint_out) `Enc_utf8;*)
350 (*        close_out xmllint_out;*)
351 (*        try*)
352 (*          while true do*)
353 (*            output_string outfile (input_line xmllint_in ^ "\n")*)
354 (*          done*)
355 (*        with End_of_file ->*)
356 (*          close_in xmllint_in;*)
357 (*          ignore (Unix.close_process (xmllint_in, xmllint_out))*)
358 (*      end else*)
359 (*        xml_root#write (`Out_channel outfile) `Enc_utf8;*)
360 (*      Unix.lockf (Unix.descr_of_out_channel outfile) Unix.F_ULOCK 0;*)
361 (*      close_out outfile*)
362
363 (* PXP version *)
364 (*let load_from_absolute =*)
365 (*  let config = PxpHelmConf.pxp_config in*)
366 (*  let entry = `Entry_document [ `Extend_dtd_fully; `Parse_xml_decl ] in*)
367 (*  let fold_key key_stack key =*)
368 (*    match key_stack with*)
369 (*    | [] -> key*)
370 (*    | _ -> String.concat "." key_stack ^ "." ^ key*)
371 (*  in*)
372 (*  fun registry fname ->*)
373 (*    debug_print ("Loading configuration from " ^ fname);*)
374 (*    let document =*)
375 (*      parse_wfdocument_entity config (from_file fname) PxpHelmConf.pxp_spec*)
376 (*    in*)
377 (*    let rec aux key_stack node =*)
378 (*      node#iter_nodes (fun n ->*)
379 (*        try*)
380 (*          (match n#node_type with*)
381 (*          | T_element "section" ->*)
382 (*              let section = n#required_string_attribute "name" in*)
383 (*              aux (key_stack @ [section]) n*)
384 (*          | T_element "key" ->*)
385 (*              let key = n#required_string_attribute "name" in*)
386 (*              let value = n#data in*)
387 (*              set registry ~key:(fold_key key_stack key) ~value*)
388 (*          | _ -> ())*)
389 (*        with exn ->*)
390 (*          let (fname, line, pos) = n#position in*)
391 (*          raise (Parse_error (fname, line, pos,*)
392 (*            "Uncaught exception: " ^ Printexc.to_string exn)))*)
393 (*    in*)
394 (*    let backup = backup_registry registry in*)
395 (*    Hashtbl.clear registry;*)
396 (*    try*)
397 (*      aux [] document#root*)
398 (*    with exn ->*)
399 (*      restore_registry backup registry;*)
400 (*      raise exn*)
401
402 (* XmlPushParser version *)
403 let load_from_absolute registry fname =
404   let path = ref [] in  (* <section> elements entered so far *)
405   let in_key = ref false in (* have we entered a <key> element? *)
406   let push_path name = path := name :: !path in
407   let pop_path () = path := List.tl !path in
408   let start_element tag attrs =
409     match tag, attrs with
410     | "section", ["name", name] -> push_path name
411     | "key", ["name", name] -> in_key := true; push_path name
412     | "helm_registry", _ -> ()
413     | tag, _ ->
414         raise (Parse_error (fname, ~-1, ~-1,
415           (sprintf "unexpected element <%s> or wrong attribute set" tag)))
416   in
417   let end_element tag =
418     match tag with
419     | "section" -> pop_path ()
420     | "key" -> in_key := false; pop_path ()
421     | "helm_registry" -> ()
422     | _ -> assert false
423   in
424   let character_data text =
425     if !in_key then
426       let key = String.concat "." (List.rev !path) in
427       let value =
428         if Hashtbl.mem registry key then
429           Hashtbl.find registry key ^ text
430         else
431           text
432       in
433       set registry ~key ~value
434   in
435   let callbacks = {
436     XmlPushParser.default_callbacks with
437       XmlPushParser.start_element = Some start_element;
438       XmlPushParser.end_element = Some end_element;
439       XmlPushParser.character_data = Some character_data;
440   } in
441   let xml_parser = XmlPushParser.create_parser callbacks in
442   let backup = backup_registry registry in
443   Hashtbl.clear registry;
444   try
445     XmlPushParser.parse xml_parser (`File fname)
446   with exn ->
447     restore_registry backup registry;
448     raise exn
449
450 let load_from registry ?path fname =
451   if Filename.is_relative fname then begin
452     let no_file_found = ref true in
453     let path =
454       match path with
455       | Some path -> path (* path given as argument *)
456       | None -> [ Sys.getcwd () ] (* no path given, try with cwd *)
457     in
458     List.iter
459       (fun dir ->
460         let conffile = dir ^ "/" ^ fname in
461         if Sys.file_exists conffile then begin
462           no_file_found := false;
463           load_from_absolute registry conffile
464         end)
465        path;
466     if !no_file_found then
467       failwith (sprintf
468         "Helm_registry.init: no configuration file named %s in [ %s ]"
469         fname (String.concat "; " path))
470   end else
471     load_from_absolute registry fname
472
473 let fold registry ?prefix ?(interpolate = true) f init =
474   let value_of k v = if interpolate then get registry k else strip_blanks v in
475   match prefix with
476   | None -> Hashtbl.fold (fun k v acc -> f acc k (value_of k v)) registry init
477   | Some s ->
478       let key_matches = starts_with (s ^ ".") in
479       let rec fold_filter acc = function
480         | [] -> acc
481         | (k,v) :: tl when key_matches k ->
482             fold_filter (f acc k (value_of k v)) tl
483         | _ :: tl -> fold_filter acc tl
484       in
485       fold_filter init (hashtbl_pairs registry)
486
487 let iter registry ?prefix ?interpolate f =
488   fold registry ?prefix ?interpolate (fun _ k v -> f k v) ()
489 let to_list registry ?prefix ?interpolate () =
490   fold registry ?prefix ?interpolate (fun acc k v -> (k, v) :: acc) []
491
492 let ls registry prefix =
493   let prefix = prefix ^ "." in
494   let prefix_len = String.length prefix in
495   let key_matches = starts_with prefix in
496   let matching_keys = (* collect matching keys' _postfixes_ *)
497     fold registry
498       (fun acc key _ ->
499         if key_matches key then
500           String.sub key prefix_len (String.length key - prefix_len) :: acc
501         else
502           acc)
503       []
504   in
505   let (sections, keys) =
506     List.fold_left
507       (fun (sections, keys) postfix ->
508         match Str.split dot_rex postfix with
509         | [key] -> (sections, key :: keys)
510         | hd_key :: _ ->  (* length > 1 => nested section found *)
511             (hd_key :: sections, keys)
512         | _ -> assert false)
513       ([], []) matching_keys
514   in
515   (list_uniq (List.sort Pervasives.compare sections), keys)
516
517 (** {2 OO interface} *)
518
519 class registry ?path fname =
520   object (self)
521     val _registry = Hashtbl.create magic_size
522     initializer load_from _registry ?path fname
523     method get = get _registry
524     method set = set _registry
525     method has = has _registry
526     method unset = unset _registry
527     method fold:
528       'a.
529         ?prefix:string -> ?interpolate: bool ->
530           ('a -> string -> string -> 'a) -> 'a -> 'a
531       =
532         fun ?prefix ?interpolate f init ->
533           fold _registry ?prefix ?interpolate f init
534     method iter = iter _registry
535     method to_list = to_list _registry
536     method ls = ls _registry
537     method get_string = get_string _registry
538     method get_int = get_int _registry
539     method get_float = get_float _registry
540     method get_bool = get_bool _registry
541     method get_string_list = get_string_list _registry
542     method set_string = set_string _registry
543     method set_int = set_int _registry
544     method set_float = set_float _registry
545     method set_bool = set_bool _registry
546     method set_string_list = set_string_list _registry
547     method get_opt: 'a. (string -> 'a) -> string -> 'a option =
548       fun getter key ->
549         try Some (getter key) with Key_not_found _ -> None
550     method set_opt:
551       'a. (key:string -> value:'a -> unit) -> key:string -> value:'a option ->
552         unit
553       =
554         fun setter ~key ~value ->
555           match value with
556           | None -> self#unset key
557           | Some value -> setter ~key ~value
558     method get_opt_default: 'a. (string -> 'a) -> 'a -> string -> 'a =
559       fun getter default key ->
560         match self#get_opt getter key with
561         | None -> default
562         | Some v -> v
563     method save_to = save_to _registry
564 (*     method load_from = load_from _registry *)
565   end
566
567 (** {2 API implementation}
568  * functional methods above are wrapped so that they work on a default
569  * (imperative) registry*)
570
571 let default_registry = Hashtbl.create magic_size
572
573 let get = get default_registry
574 let set = set default_registry
575 let has = has default_registry
576 let fold ?prefix ?interpolate f init =
577   fold default_registry ?prefix ?interpolate f init
578 let iter = iter default_registry
579 let to_list = to_list default_registry
580 let ls = ls default_registry
581 let get_string = get_string default_registry
582 let get_int = get_int default_registry
583 let get_float = get_float default_registry
584 let get_bool = get_bool default_registry
585 let get_string_list = get_string_list default_registry
586 let set_string = set_string default_registry
587 let set_int = set_int default_registry
588 let set_float = set_float default_registry
589 let set_bool = set_bool default_registry
590 let set_string_list = set_string_list default_registry
591 let get_opt getter key = try Some (getter key) with Key_not_found _ -> None
592 let set_opt setter ~key ~value =
593   match value with
594   | None -> unset default_registry key
595   | Some value -> setter ~key ~value
596 let unset = unset default_registry
597 let get_opt_default getter default key =
598   match get_opt getter key with
599   | None -> default
600   | Some v -> v
601 let save_to = save_to default_registry
602 let load_from = load_from default_registry
603