]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/getter/http_getter_env.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / getter / http_getter_env.ml
index a73710632afaf970bed9ab1cf3ef4c8c271229c6..c12709dcc562c652d41e09baac1547f44b033072 100644 (file)
@@ -33,7 +33,7 @@ open Http_getter_misc
 
 let version = Http_getter_const.version
 
-let blanks_RE = Pcre.regexp "\\s"
+let prefix_RE = Pcre.regexp "^\\s*([^\\s]+)\\s+([^\\s]+)\\s*$"
 
 let cache_dir  = lazy (normalize_dir (Helm_registry.get "getter.cache_dir"))
 let dtd_dir = lazy (normalize_dir (Helm_registry.get "getter.dtd_dir"))
@@ -54,18 +54,15 @@ let prefixes = lazy (
   let prefixes = Helm_registry.get_list Helm_registry.string "getter.prefix" in
   List.fold_left
     (fun acc prefix ->
-      match Pcre.split ~rex:blanks_RE prefix with
-      | [uri_prefix; url_prefix] -> (uri_prefix, url_prefix) :: acc
-      | _ ->
-          Http_getter_logger.log ("skipping invalid prefix: " ^ prefix);
-          acc)
+      let subs = Pcre.extract ~rex:prefix_RE prefix in
+      try
+        (subs.(1), subs.(2)) :: acc
+      with Invalid_argument _ ->
+        Http_getter_logger.log ("skipping invalid prefix: " ^ prefix);
+        acc)
     [] prefixes)
 
-let host =
-  lazy
-    (let buf = Buffer.create 20 in
-    Shell.call ~stdout:(Shell.to_buffer buf) [Shell.cmd "hostname" ["-f"]];
-    Pcre.replace ~pat:"\n+$" (Buffer.contents buf))
+let host = lazy (Http_getter_misc.backtick "hostname -f")
 
 let my_own_url =
   lazy
@@ -74,11 +71,13 @@ let my_own_url =
     host (if port = 80 then "" else (sprintf ":%d" port)))
 
 let env_to_string () =
-  let pp_prefix (uri_prefix, url_prefix) = uri_prefix ^ " -> " ^ url_prefix in
+  let pp_prefix (uri_prefix, url_prefix) =
+    "    " ^ uri_prefix ^ " -- " ^ url_prefix
+  in
   let pp_prefixes prefixes =
     match prefixes with
     | [] -> ""
-    | l -> "\n" ^ String.concat "\n" (List.map pp_prefix l) ^ "\n"
+    | l -> "\n" ^ String.concat "\n" (List.map pp_prefix l)
   in
   sprintf
 "HTTP Getter %s