]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/utils/misc.mli
update
[l4.git] / l4 / pkg / ocaml / contrib / utils / misc.mli
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
6 (*                                                                     *)
7 (*  Copyright 1996 Institut National de Recherche en Informatique et   *)
8 (*  en Automatique.  All rights reserved.  This file is distributed    *)
9 (*  under the terms of the Q Public License version 1.0.               *)
10 (*                                                                     *)
11 (***********************************************************************)
12
13 (* $Id: misc.mli 7909 2007-02-23 13:44:51Z ertai $ *)
14
15 (* Miscellaneous useful types and functions *)
16
17 val fatal_error: string -> 'a
18 exception Fatal_error
19
20 val try_finally : (unit -> 'a) -> (unit -> unit) -> 'a;;
21
22 val map_end: ('a -> 'b) -> 'a list -> 'b list -> 'b list
23         (* [map_end f l t] is [map f l @ t], just more efficient. *)
24 val map_left_right: ('a -> 'b) -> 'a list -> 'b list
25         (* Like [List.map], with guaranteed left-to-right evaluation order *)
26 val for_all2: ('a -> 'b -> bool) -> 'a list -> 'b list -> bool
27         (* Same as [List.for_all] but for a binary predicate.
28            In addition, this [for_all2] never fails: given two lists
29            with different lengths, it returns false. *)
30 val replicate_list: 'a -> int -> 'a list
31         (* [replicate_list elem n] is the list with [n] elements
32            all identical to [elem]. *)
33 val list_remove: 'a -> 'a list -> 'a list
34         (* [list_remove x l] returns a copy of [l] with the first
35            element equal to [x] removed. *)
36 val split_last: 'a list -> 'a list * 'a
37         (* Return the last element and the other elements of the given list. *)
38 val samelist: ('a -> 'a -> bool) -> 'a list -> 'a list -> bool
39         (* Like [List.for_all2] but returns [false] if the two
40            lists have different length. *)
41
42 val may: ('a -> unit) -> 'a option -> unit
43 val may_map: ('a -> 'b) -> 'a option -> 'b option
44
45 val find_in_path: string list -> string -> string
46         (* Search a file in a list of directories. *)
47 val find_in_path_uncap: string list -> string -> string
48         (* Same, but search also for uncapitalized name, i.e.
49            if name is Foo.ml, allow /path/Foo.ml and /path/foo.ml
50            to match. *)
51 val remove_file: string -> unit
52         (* Delete the given file if it exists. Never raise an error. *)
53 val expand_directory: string -> string -> string
54         (* [expand_directory alt file] eventually expands a [+] at the
55            beginning of file into [alt] (an alternate root directory) *)
56
57 val create_hashtable: int -> ('a * 'b) list -> ('a, 'b) Hashtbl.t
58         (* Create a hashtable of the given size and fills it with the
59            given bindings. *)
60
61 val copy_file: in_channel -> out_channel -> unit
62         (* [copy_file ic oc] reads the contents of file [ic] and copies
63            them to [oc]. It stops when encountering EOF on [ic]. *)
64 val copy_file_chunk: in_channel -> out_channel -> int -> unit
65         (* [copy_file_chunk ic oc n] reads [n] bytes from [ic] and copies
66            them to [oc]. It raises [End_of_file] when encountering
67            EOF on [ic]. *)
68
69 val log2: int -> int
70         (* [log2 n] returns [s] such that [n = 1 lsl s] 
71            if [n] is a power of 2*)
72 val align: int -> int -> int
73         (* [align n a] rounds [n] upwards to a multiple of [a]
74            (a power of 2). *)
75 val no_overflow_add: int -> int -> bool
76         (* [no_overflow_add n1 n2] returns [true] if the computation of
77            [n1 + n2] does not overflow. *)
78 val no_overflow_sub: int -> int -> bool
79         (* [no_overflow_add n1 n2] returns [true] if the computation of
80            [n1 - n2] does not overflow. *)
81 val no_overflow_lsl: int -> bool
82         (* [no_overflow_add n] returns [true] if the computation of
83            [n lsl 1] does not overflow. *)
84
85 val chop_extension_if_any: string -> string
86         (* Like Filename.chop_extension but returns the initial file
87            name if it has no extension *)
88
89 val chop_extensions: string -> string
90         (* Return the given file name without its extensions. The extensions
91            is the longest suffix starting with a period and not including
92            a directory separator, [.xyz.uvw] for instance.
93
94            Return the given name if it does not contain an extension. *)
95
96 val search_substring: string -> string -> int -> int
97         (* [search_substring pat str start] returns the position of the first
98            occurrence of string [pat] in string [str].  Search starts
99            at offset [start] in [str].  Raise [Not_found] if [pat]
100            does not occur. *)
101
102 val rev_split_words: string -> string list
103         (* [rev_split_words s] splits [s] in blank-separated words, and return
104            the list of words in reverse order. *)