]> 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 c09dcf2c10fefc0f8fd6b51dc1ee7b05d8b1cfd4..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 }
@@ -107,11 +112,11 @@ 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