]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/registry/helm_registry.ml
5569165a3591c96821da3377140bcc8ee2966967
[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 exception Malformed_key of string
33 exception Key_not_found of string
34 exception Cyclic_definition of string
35 exception Type_error of string * string * string (* expected type, value, msg *)
36 exception Parse_error of string * int * int * string  (* file, line, col, msg *)
37 exception Invalid_value of (string * string) * string (* key, value, descr *)
38
39 type validator_id = int
40
41   (* root XML tag: used by save_to, ignored by load_from *)
42 let root_tag = "helm_registry"
43
44 let get_next_validator_id =
45   let next_id = ref 0 in
46   fun () ->
47     incr next_id;
48     !next_id
49
50 let magic_size = 127
51 let validators = Hashtbl.create magic_size
52 let registry = Hashtbl.create magic_size
53
54 let backup_registry () = Hashtbl.copy registry
55 let restore_registry backup =
56   Hashtbl.clear registry;
57   Hashtbl.iter (fun key value -> Hashtbl.replace registry key value) backup
58
59   (* as \\w but:
60    * - no sequences of '_' longer than 1 are permitted
61    * - no uppercase letter are permitted
62    *)
63 let valid_step_rex_raw = "[a-z0-9]+\\(_[a-z0-9]+\\)*"
64 let valid_key_rex_raw =
65   sprintf "%s\(\\.%s\)*" valid_step_rex_raw valid_step_rex_raw
66 let valid_key_rex = Str.regexp ("^" ^ valid_key_rex_raw ^ "$")
67 let interpolated_key_rex = Str.regexp ("\\$(" ^ valid_key_rex_raw ^ ")")
68 let dot_rex = Str.regexp "\\."
69 let spaces_rex = Str.regexp "[ \t\n\r]+"
70 let heading_spaces_rex = Str.regexp "^[ \t\n\r]+"
71
72 let split s =
73   (* trailing blanks are removed per default by split *)
74   Str.split spaces_rex (Str.global_replace heading_spaces_rex "" s)
75 let merge l = String.concat " " l
76
77   (* escapes for xml configuration file *)
78 let (escape, unescape) =
79   let (in_enc, out_enc) = (`Enc_utf8, `Enc_utf8) in
80   (Netencoding.Html.encode ~in_enc ~out_enc (),
81    Netencoding.Html.decode ~in_enc ~out_enc ~entity_base:`Xml ())
82
83 let key_is_valid key =
84 (*   if not (Pcre.pmatch ~rex:valid_key_rex key) then *)
85   if not (Str.string_match valid_key_rex key 0) then
86     raise (Malformed_key key)
87
88 let value_is_valid ~key ~value =
89   List.iter
90     (fun (validator, descr) ->
91       if not (validator value) then
92         raise (Invalid_value ((key, value), descr)))
93     (Hashtbl.find_all validators key)
94
95 let set' registry ~key ~value =
96   debug_print (sprintf "Setting %s = %s" key value);
97   key_is_valid key;
98   value_is_valid ~key ~value;
99   Hashtbl.replace registry key value
100
101 let unset = Hashtbl.remove registry
102
103 let env_var_of_key key =
104 (*   Pcre.replace ~rex:dot_rex ~templ:"__" (String.uppercase key) *)
105   Str.global_replace dot_rex "__" (String.uppercase key)
106
107 let get key =
108   let rec aux stack key =
109     key_is_valid key;
110     if List.mem key stack then begin
111       let msg = (String.concat " -> " (List.rev stack)) ^ " -> " ^ key in
112       raise (Cyclic_definition msg)
113     end;
114     let registry_value =  (* internal value *)
115       try
116         Some (Hashtbl.find registry key)
117       with Not_found -> None
118     in
119     let env_value = (* environment value *)
120       try
121         Some (Sys.getenv (env_var_of_key key))
122       with Not_found -> None
123     in
124     let value = (* resulting value *)
125       match (registry_value, env_value) with
126       | Some reg, Some env  -> env
127       | Some reg, None      -> reg
128       | None,     Some env  -> env
129       | None,     None      -> raise (Key_not_found key)
130     in
131     interpolate (key :: stack) value
132   and interpolate stack value =
133     Str.global_substitute interpolated_key_rex
134       (fun s ->
135         let matched = Str.matched_string s in
136           (* "$(var)" -> "var" *)
137         let key = String.sub matched 2 (String.length matched - 3) in
138         aux stack key)
139       value
140   in
141   aux [] key
142
143 let set = set' registry
144
145 let mk_get_set type_name (from_string: string -> 'a) (to_string: 'a -> string) =
146   let getter key =
147     let value = get key in
148     try
149       from_string value
150     with exn ->
151       raise (Type_error (type_name, value, Printexc.to_string exn))
152   in
153   let setter ~key ~value = set ~key ~value:(to_string value) in
154   (getter, setter)
155
156 let (get_string, set_string) = (get, set)
157 let (get_int, set_int) = mk_get_set "int" int_of_string string_of_int
158 let (get_float, set_float) = mk_get_set "float" float_of_string string_of_float
159 let (get_bool, set_bool) = mk_get_set "bool" bool_of_string string_of_bool
160 let (get_string_list, set_string_list) = mk_get_set "string list" split merge
161
162 let get_opt getter key =
163   try
164     Some (getter key)
165   with Key_not_found _ -> None
166 let set_opt setter ~key ~value =
167   match value with
168   | None -> unset key
169   | Some value -> setter ~key ~value
170
171 let add_validator ~key ~validator ~descr =
172   let id = get_next_validator_id () in
173   Hashtbl.add validators key (validator, descr);
174   id
175
176 open Pxp_dtd
177 open Pxp_document
178 open Pxp_types
179 open Pxp_yacc
180
181 let save_to =
182   let dtd = new dtd default_config.warner `Enc_utf8 in
183   let dot_RE = Str.regexp "\\." in
184   let create_key_node key value = (* create a <key name="foo">value</key> *)
185     let element =
186       create_element_node ~valcheck:false default_spec dtd "key" ["name", key]
187     in
188     let data = create_data_node default_spec dtd value in
189     element#append_node data;
190     element
191   in
192   let is_section name =
193     fun node ->
194       match node#node_type with
195       | T_element "section" ->
196           (try node#attribute "name" = Value name with Not_found -> false)
197       | _ -> false
198   in
199   let add_key_node root sections key value =
200     let rec aux node = function
201       | [] ->
202           let key_node = create_key_node key value in
203           node#append_node key_node
204       | section :: tl ->
205           let next_node =
206             try
207               find ~deeply:false (is_section section) node
208             with Not_found ->
209               let section_node =
210                 create_element_node ~valcheck:false default_spec dtd
211                   "section" ["name", section]
212               in
213               node#append_node section_node;
214               section_node
215           in
216           aux next_node tl
217     in
218     aux root sections
219   in
220   fun fname ->
221     let xml_root =
222       create_element_node ~valcheck:false default_spec dtd "helm_registry" []
223     in
224     Hashtbl.iter
225       (fun key value ->
226         let sections, key =
227           let hd, tl =
228             match List.rev (Str.split dot_RE key) with
229             | hd :: tl -> hd, tl
230             | _ -> assert false
231           in
232           List.rev tl, hd
233         in
234         add_key_node xml_root sections key value)
235       registry;
236       let outchan = (* let's write xml output to fname *)
237         if Unix.system "xmllint --version &> /dev/null" = Unix.WEXITED 0 then
238           (* xmllint available, use it! *)
239           Unix.open_process_out (sprintf
240             "xmllint --format --encode utf8 -o '%s' -" fname)
241         else
242           (* xmllint not available, write pxp ugly output directly to fname *)
243           open_out fname
244       in
245       xml_root#write (`Out_channel outchan) `Enc_utf8;
246       close_out outchan
247
248 let load_from_absolute =
249   let config = default_config in
250   let entry = `Entry_document [ `Extend_dtd_fully; `Parse_xml_decl ] in
251   let fold_key key_stack key =
252     match key_stack with
253     | [] -> key
254     | _ -> String.concat "." key_stack ^ "." ^ key
255   in
256   fun fname ->
257     debug_print ("Loading configuration from " ^ fname);
258     let document =
259       parse_wfdocument_entity config (from_file fname) default_spec
260     in
261     let rec aux key_stack node =
262       node#iter_nodes (fun n ->
263         try
264           (match n#node_type with
265           | T_element "section" ->
266               let section = n#required_string_attribute "name" in
267               aux (key_stack @ [section]) n
268           | T_element "key" ->
269               let key = n#required_string_attribute "name" in
270               let value = n#data in
271               set ~key:(fold_key key_stack key) ~value
272           | _ -> ())
273         with exn ->
274           let (fname, line, pos) = n#position in
275           raise (Parse_error (fname, line, pos,
276             "Uncaught exception: " ^ Printexc.to_string exn)))
277     in
278     let backup = backup_registry () in
279     Hashtbl.clear registry;
280     try
281       aux [] document#root
282     with exn ->
283       restore_registry backup;
284       raise exn
285
286 let load_from ?path fname =
287   if Filename.is_relative fname then begin
288     let no_file_found = ref true in
289     let path =
290       match path with
291       | Some path -> path (* path given as argument *)
292       | None -> [ Sys.getcwd () ] (* no path given, try with cwd *)
293     in
294     List.iter
295       (fun dir ->
296         let conffile = dir ^ "/" ^ fname in
297         if Sys.file_exists conffile then begin
298           no_file_found := false;
299           load_from_absolute conffile
300         end)
301        path;
302     if !no_file_found then
303       failwith (sprintf
304         "Helm_registry.init: no configuration file named %s in [ %s ]"
305         fname (String.concat "; " path))
306   end else
307     load_from_absolute fname
308
309   (* DEBUGGING ONLY *)
310
311 let dump () = Hashtbl.iter (fun k v -> printf "%s = %s\n" k v) registry
312