]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/registry/helm_registry.ml
fixed some invalid backslash escapes
[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
101 let split s =
102   (* trailing blanks are removed per default by split *)
103   Str.split spaces_rex (Str.global_replace heading_spaces_rex "" s)
104 let merge l = String.concat " " l
105
106   (* escapes for xml configuration file *)
107 let (escape, unescape) =
108   let (in_enc, out_enc) = (`Enc_utf8, `Enc_utf8) in
109   (Netencoding.Html.encode ~in_enc ~out_enc (),
110    Netencoding.Html.decode ~in_enc ~out_enc ~entity_base:`Xml ())
111
112 let key_is_valid key =
113   if not (Str.string_match valid_key_rex key 0) then
114     raise (Malformed_key key)
115
116 (*
117 let value_is_valid ~key ~value =
118   List.iter
119     (fun (validator, descr) ->
120       if not (validator value) then
121         raise (Invalid_value ((key, value), descr)))
122     (Hashtbl.find_all validators key)
123 *)
124
125 let set' registry ~key ~value =
126   debug_print (sprintf "Setting %s = %s" key value);
127   key_is_valid key;
128 (*   value_is_valid ~key ~value; *)
129   Hashtbl.replace registry key value
130
131 let unset registry = Hashtbl.remove registry
132
133 let env_var_of_key = Str.global_replace dot_rex "__"
134
135 let get registry key =
136   let rec aux stack key =
137     key_is_valid key;
138     if List.mem key stack then begin
139       let msg = (String.concat " -> " (List.rev stack)) ^ " -> " ^ key in
140       raise (Cyclic_definition msg)
141     end;
142     let registry_value =  (* internal value *)
143       try
144         Some (Hashtbl.find registry key)
145       with Not_found -> None
146     in
147     let env_value = (* environment value *)
148       try
149         Some (Sys.getenv (env_var_of_key key))
150       with Not_found -> None
151     in
152     let value = (* resulting value *)
153       match (registry_value, env_value) with
154       | Some reg, Some env  -> env
155       | Some reg, None      -> reg
156       | None,     Some env  -> env
157       | None,     None      -> raise (Key_not_found key)
158     in
159     interpolate (key :: stack) value
160   and interpolate stack value =
161     Str.global_substitute interpolated_key_rex
162       (fun s ->
163         let matched = Str.matched_string s in
164           (* "$(var)" -> "var" *)
165         let key = String.sub matched 2 (String.length matched - 3) in
166         aux stack key)
167       value
168   in
169   aux [] key
170
171 let set registry = set' registry
172
173 let has registry key = Hashtbl.mem registry key
174
175 let mk_get_set type_name
176   (from_string: string -> 'a) (to_string: 'a -> string)
177   =
178   let getter registry key =
179     let value = get registry key in
180     try
181       from_string value
182     with exn ->
183       raise (Type_error (type_name, value, Printexc.to_string exn))
184   in
185   let setter registry ~key ~value =
186     set registry ~key ~value:(to_string value)
187   in
188   (getter, setter)
189
190 let (get_string, set_string) = (get, set)
191 let (get_int, set_int) = mk_get_set "int" int_of_string string_of_int
192 let (get_float, set_float) = mk_get_set "float" float_of_string string_of_float
193 let (get_bool, set_bool) = mk_get_set "bool" bool_of_string string_of_bool
194 let (get_string_list, set_string_list) = mk_get_set "string list" split merge
195
196 let get_opt registry getter key =
197   try
198     Some (getter registry key)
199   with Key_not_found _ -> None
200 let set_opt registry setter ~key ~value =
201   match value with
202   | None -> unset registry key
203   | Some value -> setter registry ~key ~value
204 let get_opt_default registry getter default key =
205   match get_opt registry getter key with
206   | None -> default
207   | Some v -> v
208
209 (*
210 let add_validator ~key ~validator ~descr =
211   let id = get_next_validator_id () in
212   Hashtbl.add validators key (validator, descr);
213   id
214 *)
215
216 open Pxp_dtd
217 open Pxp_document
218 open Pxp_types
219 open Pxp_yacc
220
221 let save_to =
222   let dtd = new dtd PxpHelmConf.pxp_config.warner `Enc_utf8 in
223   let dot_RE = Str.regexp "\\." in
224   let create_key_node key value = (* create a <key name="foo">value</key> *)
225     let element =
226       create_element_node ~valcheck:false PxpHelmConf.pxp_spec dtd
227         "key" ["name", key]
228     in
229     let data = create_data_node PxpHelmConf.pxp_spec dtd value in
230     element#append_node data;
231     element
232   in
233   let is_section name =
234     fun node ->
235       match node#node_type with
236       | T_element "section" ->
237           (try node#attribute "name" = Value name with Not_found -> false)
238       | _ -> false
239   in
240   let add_key_node root sections key value =
241     let rec aux node = function
242       | [] ->
243           let key_node = create_key_node key value in
244           node#append_node key_node
245       | section :: tl ->
246           let next_node =
247             try
248               find ~deeply:false (is_section section) node
249             with Not_found ->
250               let section_node =
251                 create_element_node ~valcheck:false PxpHelmConf.pxp_spec dtd
252                   "section" ["name", section]
253               in
254               node#append_node section_node;
255               section_node
256           in
257           aux next_node tl
258     in
259     aux root sections
260   in
261   fun registry fname ->
262     let xml_root =
263       create_element_node ~valcheck:false PxpHelmConf.pxp_spec dtd
264       "helm_registry" []
265     in
266     Hashtbl.iter
267       (fun key value ->
268         let sections, key =
269           let hd, tl =
270             match List.rev (Str.split dot_RE key) with
271             | hd :: tl -> hd, tl
272             | _ -> assert false
273           in
274           List.rev tl, hd
275         in
276         add_key_node xml_root sections key value)
277       registry;
278       let outfile = open_out fname in
279       Unix.lockf (Unix.descr_of_out_channel outfile) Unix.F_LOCK 0; (* blocks *)
280       if
281         Unix.system "xmllint --version &> /dev/null" = Unix.WEXITED 0
282       then begin
283         let (xmllint_in, xmllint_out) =
284           Unix.open_process "xmllint --format --encode utf8 -"
285         in
286         xml_root#write (`Out_channel xmllint_out) `Enc_utf8;
287         close_out xmllint_out;
288         try
289           while true do
290             output_string outfile (input_line xmllint_in ^ "\n")
291           done
292         with End_of_file ->
293           close_in xmllint_in;
294           ignore (Unix.close_process (xmllint_in, xmllint_out))
295       end else
296         xml_root#write (`Out_channel outfile) `Enc_utf8;
297       Unix.lockf (Unix.descr_of_out_channel outfile) Unix.F_ULOCK 0;
298       close_out outfile
299
300 let load_from_absolute =
301   let config = PxpHelmConf.pxp_config in
302   let entry = `Entry_document [ `Extend_dtd_fully; `Parse_xml_decl ] in
303   let fold_key key_stack key =
304     match key_stack with
305     | [] -> key
306     | _ -> String.concat "." key_stack ^ "." ^ key
307   in
308   fun registry fname ->
309     debug_print ("Loading configuration from " ^ fname);
310     let document =
311       parse_wfdocument_entity config (from_file fname) PxpHelmConf.pxp_spec
312     in
313     let rec aux key_stack node =
314       node#iter_nodes (fun n ->
315         try
316           (match n#node_type with
317           | T_element "section" ->
318               let section = n#required_string_attribute "name" in
319               aux (key_stack @ [section]) n
320           | T_element "key" ->
321               let key = n#required_string_attribute "name" in
322               let value = n#data in
323               set registry ~key:(fold_key key_stack key) ~value
324           | _ -> ())
325         with exn ->
326           let (fname, line, pos) = n#position in
327           raise (Parse_error (fname, line, pos,
328             "Uncaught exception: " ^ Printexc.to_string exn)))
329     in
330     let backup = backup_registry registry in
331     Hashtbl.clear registry;
332     try
333       aux [] document#root
334     with exn ->
335       restore_registry backup registry;
336       raise exn
337
338 let load_from registry ?path fname =
339   if Filename.is_relative fname then begin
340     let no_file_found = ref true in
341     let path =
342       match path with
343       | Some path -> path (* path given as argument *)
344       | None -> [ Sys.getcwd () ] (* no path given, try with cwd *)
345     in
346     List.iter
347       (fun dir ->
348         let conffile = dir ^ "/" ^ fname in
349         if Sys.file_exists conffile then begin
350           no_file_found := false;
351           load_from_absolute registry conffile
352         end)
353        path;
354     if !no_file_found then
355       failwith (sprintf
356         "Helm_registry.init: no configuration file named %s in [ %s ]"
357         fname (String.concat "; " path))
358   end else
359     load_from_absolute registry fname
360
361 let fold registry ?prefix f init =
362   match prefix with
363   | None -> Hashtbl.fold (fun k v acc -> f acc k v) registry init
364   | Some s ->
365       let key_matches = starts_with (s ^ ".") in
366       let rec fold_filter acc = function
367         | [] -> acc
368         | (k,v) :: tl when key_matches k -> fold_filter (f acc k v) tl
369         | _ :: tl -> fold_filter acc tl
370       in
371       fold_filter init (hashtbl_pairs registry)
372
373 let iter registry ?prefix f = fold registry ?prefix (fun _ k v -> f k v) ()
374 let to_list registry ?prefix () =
375   fold registry ?prefix (fun acc k v -> (k, v) :: acc) []
376
377 let ls registry prefix =
378   let prefix = prefix ^ "." in
379   let prefix_len = String.length prefix in
380   let key_matches = starts_with prefix in
381   let matching_keys = (* collect matching keys' _postfixes_ *)
382     fold registry
383       (fun acc key _ ->
384         if key_matches key then
385           String.sub key prefix_len (String.length key - prefix_len) :: acc
386         else
387           acc)
388       []
389   in
390   let (sections, keys) =
391     List.fold_left
392       (fun (sections, keys) postfix ->
393         match Str.split dot_rex postfix with
394         | [key] -> (sections, key :: keys)
395         | hd_key :: _ ->  (* length > 1 => nested section found *)
396             (hd_key :: sections, keys)
397         | _ -> assert false)
398       ([], []) matching_keys
399   in
400   (list_uniq (List.sort Pervasives.compare sections), keys)
401
402 (** {2 OO interface} *)
403
404 class registry ?path fname =
405   object (self)
406     val _registry = Hashtbl.create magic_size
407     initializer load_from _registry ?path fname
408     method get = get _registry
409     method set = set _registry
410     method has = has _registry
411     method unset = unset _registry
412     method fold:
413       'a. ?prefix:string -> ('a -> string -> string -> 'a) -> 'a -> 'a
414       =
415         fold _registry
416     method iter = iter _registry
417     method to_list = to_list _registry
418     method ls = ls _registry
419     method get_string = get_string _registry
420     method get_int = get_int _registry
421     method get_float = get_float _registry
422     method get_bool = get_bool _registry
423     method get_string_list = get_string_list _registry
424     method set_string = set_string _registry
425     method set_int = set_int _registry
426     method set_float = set_float _registry
427     method set_bool = set_bool _registry
428     method set_string_list = set_string_list _registry
429     method get_opt: 'a. (string -> 'a) -> string -> 'a option =
430       fun getter key ->
431         try Some (getter key) with Key_not_found _ -> None
432     method set_opt:
433       'a. (key:string -> value:'a -> unit) -> key:string -> value:'a option ->
434         unit
435       =
436         fun setter ~key ~value ->
437           match value with
438           | None -> self#unset key
439           | Some value -> setter ~key ~value
440     method get_opt_default: 'a. (string -> 'a) -> 'a -> string -> 'a =
441       fun getter default key ->
442         match self#get_opt getter key with
443         | None -> default
444         | Some v -> v
445     method save_to = save_to _registry
446 (*     method load_from = load_from _registry *)
447   end
448
449 (** {2 API implementation}
450  * functional methods above are wrapped so that they work on a default
451  * (imperative) registry*)
452
453 let default_registry = Hashtbl.create magic_size
454
455 let get = get default_registry
456 let set = set default_registry
457 let has = has default_registry
458 let fold ?prefix f init = fold default_registry ?prefix f init
459 let iter = iter default_registry
460 let to_list = to_list default_registry
461 let ls = ls default_registry
462 let get_string = get_string default_registry
463 let get_int = get_int default_registry
464 let get_float = get_float default_registry
465 let get_bool = get_bool default_registry
466 let get_string_list = get_string_list default_registry
467 let set_string = set_string default_registry
468 let set_int = set_int default_registry
469 let set_float = set_float default_registry
470 let set_bool = set_bool default_registry
471 let set_string_list = set_string_list default_registry
472 let get_opt getter key = try Some (getter key) with Key_not_found _ -> None
473 let set_opt setter ~key ~value =
474   match value with
475   | None -> unset default_registry key
476   | Some value -> setter ~key ~value
477 let unset = unset default_registry
478 let get_opt_default getter default key =
479   match get_opt getter key with
480   | None -> default
481   | Some v -> v
482 let save_to = save_to default_registry
483 let load_from = load_from default_registry
484