]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/extlib/hExtlib.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / extlib / hExtlib.ml
index 052205da823f3a524375eb32304fa1947af3c305..a76a5c76e8252dcb7eb734a7ca4a55122a2971d8 100644 (file)
 
 (** PROFILING *)
 
+(* we should use a key in te registry, but we can't see the registry.. *)
 let profiling_enabled = true
 
+let profiling_printings = ref (fun () -> true)
+let set_profiling_printings f = profiling_printings := f
+
 type profiler = { profile : 'a 'b. ('a -> 'b) -> 'a -> 'b }
 let profile ?(enable = true) =
- if profiling_enabled && enable then
+ if profiling_enabled  && enable then
   function s ->
    let total = ref 0.0 in
    let profile f x =
@@ -48,8 +52,9 @@ let profile ?(enable = true) =
    in
    at_exit
     (fun () ->
-      print_endline
-       ("!! TOTAL TIME SPENT IN " ^ s ^ ": " ^ string_of_float !total));
+      if !profiling_printings () then
+        prerr_endline
+         ("!! TOTAL TIME SPENT IN " ^ s ^ ": " ^ string_of_float !total));
    { profile = profile }
  else
   function _ -> { profile = fun f x -> f x }
@@ -89,13 +94,29 @@ let trim_blanks s =
   let left, right = find_left 0, find_right (s_len - 1) in
   String.sub s left (right - left + 1)
 
+(** {2 Char processing} *)
+
+let is_alpha c =
+  let code = Char.code c in 
+  (code >= 65 && code <= 90) || (code >= 97 && code <= 122)
+
+let is_digit c =
+  let code = Char.code c in 
+  code >= 48 && code <= 57
+
+let is_blank c =
+  let code = Char.code c in 
+  code = 9 || code = 10 || code = 13 || code = 32
+
+let is_alphanum c = is_alpha c || is_digit c
+
 (** {2 List processing} *)
 
-let rec list_uniq = function 
+let rec list_uniq ?(eq=(=)) = function 
   | [] -> []
   | h::[] -> [h]
-  | h1::h2::tl when h1 = h2 -> list_uniq (h2 :: tl) 
-  | h1::tl (* when h1 <> h2 *) -> h1 :: list_uniq tl
+  | h1::h2::tl when eq h1 h2 -> list_uniq ~eq (h2 :: tl) 
+  | h1::tl (* when h1 <> h2 *) -> h1 :: list_uniq ~eq tl
 
 let rec filter_map f =
   function
@@ -171,6 +192,57 @@ let output_file ~filename ~text =
   let oc = open_out filename in
   output_string oc text;
   close_out oc
+
+let blank_split s =
+  let len = String.length s in
+  let buf = Buffer.create 0 in
+  let rec aux acc i =
+    if i >= len
+    then begin
+      if Buffer.length buf > 0
+      then List.rev (Buffer.contents buf :: acc)
+      else List.rev acc
+    end else begin
+      if is_blank s.[i] then
+        if Buffer.length buf > 0 then begin
+          let s = Buffer.contents buf in
+          Buffer.clear buf;
+          aux (s :: acc) (i + 1)
+        end else
+          aux acc (i + 1)
+      else begin
+        Buffer.add_char buf s.[i];
+        aux acc (i + 1)
+      end
+    end
+  in
+  aux [] 0
+
+  (* Rules: * "~name" -> home dir of "name"
+   * "~" -> value of $HOME if defined, home dir of the current user otherwise *)
+let tilde_expand s =
+  let get_home login = (Unix.getpwnam login).Unix.pw_dir in
+  let expand_one s =
+    let len = String.length s in
+    if len > 0 && s.[0] = '~' then begin
+      let login_len = ref 1 in
+      while !login_len < len && is_alphanum (s.[!login_len]) do
+        incr login_len
+      done;
+      let login = String.sub s 1 (!login_len - 1) in
+      try
+        let home =
+          if login = "" then
+            try Sys.getenv "HOME" with Not_found -> get_home (Unix.getlogin ())
+          else
+            get_home login
+        in
+        home ^ String.sub s !login_len (len - !login_len)
+      with Not_found | Invalid_argument _ -> s
+    end else
+      s
+  in
+  String.concat " " (List.map expand_one (blank_split s))
   
 let find ?(test = fun _ -> true) path = 
   let rec aux acc todo =