]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/registry/helm_registry.ml
use PxpHelmConf module
[helm.git] / helm / ocaml / registry / helm_registry.ml
index 91fcb67b57225510425da96f47d2f58d10beebaf..0c7b437238d1e57c23a9d5bcf73d83d6e4fde2b1 100644 (file)
@@ -167,42 +167,90 @@ let set_opt setter ~key ~value =
   match value with
   | None -> unset key
   | Some value -> setter ~key ~value
-
-(*
-let save_to =
-  let dtd = new dtd default_config.warner `Enc_utf8 in
-  let rec create_key node sections key value =
-    match sections with
-    | [] -> create_element_node ~valcheck:false default_spec dtd
-*)
-
-let save_to fname =
-  debug_print ("Saving configuration to " ^ fname);
-  let oc = open_out fname in
-  output_string oc "<?xml version=\"1.0\" encoding=\"utf-8\"?>\n";
-  output_string oc "<helm_registry>\n";
-  try
-    Hashtbl.iter
-      (fun key value ->
-        fprintf oc "  <value key=\"%s\">%s</value>\n" key (escape value))
-      registry;
-    output_string oc "</helm_registry>";
-    close_out oc
-  with e ->
-    close_out oc;
-    raise e
+let get_opt_default getter default key =
+  match get_opt getter key with
+  | None -> default
+  | Some v -> v
 
 let add_validator ~key ~validator ~descr =
   let id = get_next_validator_id () in
   Hashtbl.add validators key (validator, descr);
   id
 
+open Pxp_dtd
 open Pxp_document
 open Pxp_types
 open Pxp_yacc
 
+let save_to =
+  let dtd = new dtd PxpHelmConf.pxp_config.warner `Enc_utf8 in
+  let dot_RE = Str.regexp "\\." in
+  let create_key_node key value = (* create a <key name="foo">value</key> *)
+    let element =
+      create_element_node ~valcheck:false PxpHelmConf.pxp_spec dtd "key" ["name", key]
+    in
+    let data = create_data_node PxpHelmConf.pxp_spec dtd value in
+    element#append_node data;
+    element
+  in
+  let is_section name =
+    fun node ->
+      match node#node_type with
+      | T_element "section" ->
+          (try node#attribute "name" = Value name with Not_found -> false)
+      | _ -> false
+  in
+  let add_key_node root sections key value =
+    let rec aux node = function
+      | [] ->
+          let key_node = create_key_node key value in
+          node#append_node key_node
+      | section :: tl ->
+          let next_node =
+            try
+              find ~deeply:false (is_section section) node
+            with Not_found ->
+              let section_node =
+                create_element_node ~valcheck:false PxpHelmConf.pxp_spec dtd
+                  "section" ["name", section]
+              in
+              node#append_node section_node;
+              section_node
+          in
+          aux next_node tl
+    in
+    aux root sections
+  in
+  fun fname ->
+    let xml_root =
+      create_element_node ~valcheck:false PxpHelmConf.pxp_spec dtd "helm_registry" []
+    in
+    Hashtbl.iter
+      (fun key value ->
+        let sections, key =
+          let hd, tl =
+            match List.rev (Str.split dot_RE key) with
+            | hd :: tl -> hd, tl
+            | _ -> assert false
+          in
+          List.rev tl, hd
+        in
+        add_key_node xml_root sections key value)
+      registry;
+      let outchan = (* let's write xml output to fname *)
+        if Unix.system "xmllint --version &> /dev/null" = Unix.WEXITED 0 then
+          (* xmllint available, use it! *)
+          Unix.open_process_out (sprintf
+            "xmllint --format --encode utf8 -o '%s' -" fname)
+        else
+          (* xmllint not available, write pxp ugly output directly to fname *)
+          open_out fname
+      in
+      xml_root#write (`Out_channel outchan) `Enc_utf8;
+      close_out outchan
+
 let load_from_absolute =
-  let config = default_config in
+  let config = PxpHelmConf.pxp_config in
   let entry = `Entry_document [ `Extend_dtd_fully; `Parse_xml_decl ] in
   let fold_key key_stack key =
     match key_stack with
@@ -212,7 +260,7 @@ let load_from_absolute =
   fun fname ->
     debug_print ("Loading configuration from " ^ fname);
     let document =
-      parse_wfdocument_entity config (from_file fname) default_spec
+      parse_wfdocument_entity config (from_file fname) PxpHelmConf.pxp_spec
     in
     let rec aux key_stack node =
       node#iter_nodes (fun n ->