(* Copyright (C) 2005, HELM Team. * * This file is part of HELM, an Hypertextual, Electronic * Library of Mathematics, developed at the Computer Science * Department, University of Bologna, Italy. * * HELM is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License * as published by the Free Software Foundation; either version 2 * of the License, or (at your option) any later version. * * HELM is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * GNU General Public License for more details. * * You should have received a copy of the GNU General Public License * along with HELM; if not, write to the Free Software * Foundation, Inc., 59 Temple Place - Suite 330, Boston, * MA 02111-1307, USA. * * For details, see the HELM World-Wide-Web page, * http://cs.unibo.it/helm/. *) (** PROFILING *) let profiling_enabled = true type profiler = { profile : 'a 'b. ('a -> 'b) -> 'a -> 'b } let profile = if profiling_enabled then function s -> let total = ref 0.0 in let profile f x = let before = Unix.gettimeofday () in try let res = f x in let after = Unix.gettimeofday () in total := !total +. (after -. before); res with exc -> let after = Unix.gettimeofday () in total := !total +. (after -. before); raise exc in at_exit (fun () -> print_endline ("!! TOTAL TIME SPENT IN " ^ s ^ ": " ^ string_of_float !total)); { profile = profile } else function _ -> { profile = fun f x -> f x } (** {2 Optional values} *) let map_option f = function None -> None | Some v -> Some (f v) let iter_option f = function None -> () | Some v -> f v let unopt = function None -> failwith "unopt: None" | Some v -> v (** {2 String processing} *) let split ?(sep = ' ') s = let pieces = ref [] in let rec aux idx = match (try Some (String.index_from s idx sep) with Not_found -> None) with | Some pos -> pieces := String.sub s idx (pos - idx) :: !pieces; aux (pos + 1) | None -> pieces := String.sub s idx (String.length s - idx) :: !pieces in aux 0; List.rev !pieces let trim_blanks s = let rec find_left idx = match s.[idx] with | ' ' | '\t' | '\r' | '\n' -> find_left (idx + 1) | _ -> idx in let rec find_right idx = match s.[idx] with | ' ' | '\t' | '\r' | '\n' -> find_right (idx - 1) | _ -> idx in let s_len = String.length s in let left, right = find_left 0, find_right (s_len - 1) in String.sub s left (right - left + 1) (** {2 List processing} *) let rec list_uniq = function | [] -> [] | h::[] -> [h] | h1::h2::tl when h1 = h2 -> list_uniq (h2 :: tl) | h1::tl (* when h1 <> h2 *) -> h1 :: list_uniq tl let rec filter_map f = function | [] -> [] | hd :: tl -> (match f hd with | None -> filter_map f tl | Some v -> v :: filter_map f tl) let list_concat ?(sep = []) = let rec aux acc = function | [] -> [] | [ last ] -> List.flatten (List.rev (last :: acc)) | hd :: tl -> aux ([sep; hd] @ acc) tl in aux [] (** {2 File predicates} *) let is_dir fname = try (Unix.stat fname).Unix.st_kind = Unix.S_DIR with Unix.Unix_error _ -> false let is_regular fname = try (Unix.stat fname).Unix.st_kind = Unix.S_REG with Unix.Unix_error _ -> false let mkdir path = let components = split ~sep:'/' path in let rec aux where = function | [] -> () | piece::tl -> let path = where ^ "/" ^ piece in (try Unix.mkdir path 0o755 with | Unix.Unix_error (Unix.EEXIST,_,_) -> () | Unix.Unix_error (e,_,_) -> raise (Failure ("Unix.mkdir " ^ path ^ " 0o755 :" ^ (Unix.error_message e)))); aux path tl in aux "" components (** {2 Filesystem} *) let input_file fname = let size = (Unix.stat fname).Unix.st_size in let buf = Buffer.create size in let ic = open_in fname in Buffer.add_channel buf ic size; close_in ic; Buffer.contents buf let input_all ic = let size = 10240 in let buf = Buffer.create size in let s = String.create size in (try while true do let bytes = input ic s 0 size in if bytes = 0 then raise End_of_file else Buffer.add_substring buf s 0 bytes done with End_of_file -> ()); Buffer.contents buf let output_file ~filename ~text = let oc = open_out filename in output_string oc text; close_out oc let find ?(test = fun _ -> true) path = let rec aux acc todo = match todo with | [] -> acc | path :: tl -> try let handle = Unix.opendir path in let dirs = ref [] in let matching_files = ref [] in (try while true do match Unix.readdir handle with | "." | ".." -> () | entry -> let qentry = path ^ "/" ^ entry in (try if is_dir qentry then dirs := qentry :: !dirs else if test qentry then matching_files := qentry :: !matching_files; with Unix.Unix_error _ -> ()) done with End_of_file -> Unix.closedir handle); aux (!matching_files @ acc) (!dirs @ tl) with Unix.Unix_error _ -> aux acc tl in aux [] [path] (** {2 Exception handling} *) let finally at_end f arg = let res = try f arg with exn -> at_end (); raise exn in at_end (); res