93 lines
4.4 KiB
OCaml
93 lines
4.4 KiB
OCaml
(***********************************************************************)
|
|
(* *)
|
|
(* Objective Caml *)
|
|
(* *)
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
(* *)
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
|
(* under the terms of the Q Public License version 1.0. *)
|
|
(* *)
|
|
(***********************************************************************)
|
|
|
|
(* $Id$ *)
|
|
|
|
(* Miscellaneous useful types and functions *)
|
|
|
|
val fatal_error: string -> 'a
|
|
exception Fatal_error
|
|
|
|
val map_end: ('a -> 'b) -> 'a list -> 'b list -> 'b list
|
|
(* [map_end f l t] is [map f l @ t], just more efficient. *)
|
|
val map_left_right: ('a -> 'b) -> 'a list -> 'b list
|
|
(* Like [List.map], with guaranteed left-to-right evaluation order *)
|
|
val for_all2: ('a -> 'b -> bool) -> 'a list -> 'b list -> bool
|
|
(* Same as [List.for_all] but for a binary predicate.
|
|
In addition, this [for_all2] never fails: given two lists
|
|
with different lengths, it returns false. *)
|
|
val replicate_list: 'a -> int -> 'a list
|
|
(* [replicate_list elem n] is the list with [n] elements
|
|
all identical to [elem]. *)
|
|
val list_remove: 'a -> 'a list -> 'a list
|
|
(* [list_remove x l] returns a copy of [l] with the first
|
|
element equal to [x] removed. *)
|
|
val split_last: 'a list -> 'a list * 'a
|
|
(* Return the last element and the other elements of the given list. *)
|
|
|
|
val may: ('a -> unit) -> 'a option -> unit
|
|
val may_map: ('a -> 'b) -> 'a option -> 'b option
|
|
|
|
val find_in_path: string list -> string -> string
|
|
(* Search a file in a list of directories. *)
|
|
val find_in_path_uncap: string list -> string -> string
|
|
(* Same, but search also for uncapitalized name, i.e.
|
|
if name is Foo.ml, allow /path/Foo.ml and /path/foo.ml
|
|
to match. *)
|
|
val remove_file: string -> unit
|
|
(* Delete the given file if it exists. Never raise an error. *)
|
|
val expand_directory: string -> string -> string
|
|
(* [expand_directory alt file] eventually expands a [+] at the
|
|
beginning of file into [alt] (an alternate root directory) *)
|
|
|
|
val create_hashtable: int -> ('a * 'b) list -> ('a, 'b) Hashtbl.t
|
|
(* Create a hashtable of the given size and fills it with the
|
|
given bindings. *)
|
|
|
|
val copy_file: in_channel -> out_channel -> unit
|
|
(* [copy_file ic oc] reads the contents of file [ic] and copies
|
|
them to [oc]. It stops when encountering EOF on [ic]. *)
|
|
val copy_file_chunk: in_channel -> out_channel -> int -> unit
|
|
(* [copy_file_chunk ic oc n] reads [n] bytes from [ic] and copies
|
|
them to [oc]. It raises [End_of_file] when encountering
|
|
EOF on [ic]. *)
|
|
|
|
val log2: int -> int
|
|
(* [log2 n] returns [s] such that [n = 1 lsl s]
|
|
if [n] is a power of 2*)
|
|
val align: int -> int -> int
|
|
(* [align n a] rounds [n] upwards to a multiple of [a]
|
|
(a power of 2). *)
|
|
val no_overflow_add: int -> int -> bool
|
|
(* [no_overflow_add n1 n2] returns [true] if the computation of
|
|
[n1 + n2] does not overflow. *)
|
|
val no_overflow_sub: int -> int -> bool
|
|
(* [no_overflow_add n1 n2] returns [true] if the computation of
|
|
[n1 - n2] does not overflow. *)
|
|
val no_overflow_lsl: int -> bool
|
|
(* [no_overflow_add n] returns [true] if the computation of
|
|
[n lsl 1] does not overflow. *)
|
|
|
|
val chop_extension_if_any: string -> string
|
|
(* Like Filename.chop_extension but returns the initial file
|
|
name if it has no extension *)
|
|
|
|
val search_substring: string -> string -> int -> int
|
|
(* [search_substring pat str start] returns the position of the first
|
|
occurrence of string [pat] in string [str]. Search starts
|
|
at offset [start] in [str]. Raise [Not_found] if [pat]
|
|
does not occur. *)
|
|
|
|
val rev_split_words: string -> string list
|
|
(* [rev_split_words s] splits [s] in blank-separated words, and return
|
|
the list of words in reverse order. *)
|