summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib')
-rw-r--r--stdlib/arg.mli10
-rw-r--r--stdlib/array.mli61
-rw-r--r--stdlib/char.mli12
-rw-r--r--stdlib/filename.mli2
-rw-r--r--stdlib/format.mli2
-rw-r--r--stdlib/gc.mli6
-rw-r--r--stdlib/hashtbl.mli22
-rw-r--r--stdlib/lexing.mli2
-rw-r--r--stdlib/list.ml4
-rw-r--r--stdlib/list.mli81
-rw-r--r--stdlib/map.mli40
-rw-r--r--stdlib/obj.mli4
-rw-r--r--stdlib/parsing.mli8
-rw-r--r--stdlib/pervasives.ml4
-rw-r--r--stdlib/pervasives.mli418
-rw-r--r--stdlib/printexc.mli6
-rw-r--r--stdlib/printf.mli2
-rw-r--r--stdlib/queue.mli6
-rw-r--r--stdlib/set.mli48
-rw-r--r--stdlib/sort.mli2
-rw-r--r--stdlib/stack.mli6
-rw-r--r--stdlib/string.mli45
-rw-r--r--stdlib/sys.mli66
23 files changed, 732 insertions, 125 deletions
diff --git a/stdlib/arg.mli b/stdlib/arg.mli
index 593d5b36b..57ce2b3ab 100644
--- a/stdlib/arg.mli
+++ b/stdlib/arg.mli
@@ -1,4 +1,4 @@
-(* Parsing of command line arguments. *)
+(* Module [Arg]: parsing of command line arguments *)
(* This module provides a general mechanism for extracting options and
arguments from the command line to the program. *)
@@ -6,10 +6,10 @@
(* Syntax of command lines:
A keyword is a character string starting with a [-].
An option is a keyword alone or followed by an argument.
- There are four types of keywords: Unit, String, Int, and Float.
- Unit keywords do not take an argument.
- String, Int, and Float keywords take the following word on the command line
- as an argument.
+ There are four types of keywords: [Unit], [String], [Int], and [Float].
+ [Unit] keywords do not take an argument.
+ [String], [Int], and [Float] keywords take the following word on the
+ command line as an argument.
Arguments not preceded by a keyword are called anonymous arguments. *)
(* Examples ([cmd] is assumed to be the command name):
diff --git a/stdlib/array.mli b/stdlib/array.mli
index 04968bce9..17e59e1a3 100644
--- a/stdlib/array.mli
+++ b/stdlib/array.mli
@@ -1,20 +1,79 @@
-(* Array operations *)
+(* Module [Array]: array operations *)
external length : 'a array -> int = "%array_length"
+ (* Return the length (number of elements) of the given array. *)
external get: 'a array -> int -> 'a = "%array_safe_get"
+ (* [Array.get a n] returns the element number [n] of array [a].
+ The first element has number 0.
+ The last element has number [Array.length a - 1].
+ Raise [Invalid_argument "Array.get"] if [n] is outside the range
+ 0 to [(Array.length a - 1)].
+ You can also write [a.(n)] instead of [vect_item a n]. *)
external set: 'a array -> int -> 'a -> unit = "%array_safe_set"
+ (* [Array.set a n x] modifies array [a] in place, replacing
+ element number [n] with [x].
+ Raise [Invalid_argument "Array.set"] if [n] is outside the range
+ 0 to [Array.length a - 1].
+ You can also write [a.(n) <- x] instead of [vect_assign a n x]. *)
external new: int -> 'a -> 'a array = "make_vect"
+ (* [Array.new n x] returns a fresh array of length [n],
+ initialized with [x].
+ All the elements of this new array are initially
+ physically equal to [x] (in the sense of the [==] predicate).
+ Consequently, if [x] is mutable, it is shared among all elements
+ of the array, and modifying [x] through one of the array entries
+ will modify all other entries at the same time. *)
val new_matrix: int -> int -> 'a -> 'a array array
+ (* [Array.new_matrix dimx dimy e] returns a two-dimensional array
+ (an array of arrays) with first dimension [dimx] and
+ second dimension [dimy]. All the elements of this new matrix
+ are initially physically equal to [e].
+ The element ([x,y]) of a matrix [m] is accessed
+ with the notation [m.(x).(y)]. *)
val append: 'a array -> 'a array -> 'a array
+ (* [Array.append v1 v2] returns a fresh array containing the
+ concatenation of arrays [v1] and [v2]. *)
val concat: 'a array list -> 'a array
+ (* Same as [Array.append], but catenates a list of arrays. *)
val sub: 'a array -> int -> int -> 'a array
+ (* [Array.sub a start len] returns a fresh array of length [len],
+ containing the elements number [start] to [start + len - 1]
+ of array [a].
+ Raise [Invalid_argument "Array.sub"] if [start] and [len] do not
+ designate a valid subarray of [a]; that is, if
+ [start < 0], or [len < 0], or [start + len > Array.length a]. *)
val copy: 'a array -> 'a array
+ (* [Array.copy a] returns a copy of [a], that is, a fresh array
+ containing the same elements as [a]. *)
val fill: 'a array -> int -> int -> 'a -> unit
+ (* [Array.fill a ofs len x] modifies the array [a] in place,
+ storing [x] in elements number [ofs] to [ofs + len - 1].
+ Raise [Invalid_argument "Array.fill"] if [ofs] and [len] do not
+ designate a valid subarray of [a]. *)
val blit: 'a array -> int -> 'a array -> int -> int -> unit
+ (* [Array.blit v1 o1 v2 o2 len] copies [len] elements
+ from array [v1], starting at element number [o1], to array [v2],
+ starting at element number [o2]. It works correctly even if
+ [v1] and [v2] are the same array, and the source and
+ destination chunks overlap.
+ Raise [Invalid_argument "Array.blit"] if [o1] and [len] do not
+ designate a valid subarray of [v1], or if [o2] and [len] do not
+ designate a valid subarray of [v2]. *)
val iter: ('a -> 'b) -> 'a array -> unit
+ (* [Array.iter f a] applies function [f] in turn to all
+ the elements of [a], discarding all the results:
+ [f a.(0); f a.(1); ...; f a.(Array.length a - 1); ()]. *)
val map: ('a -> 'b) -> 'a array -> 'b array
+ (* [Array.map f a] applies function [f] to all the elements of [a],
+ and builds an array with the results returned by [f]:
+ [[| f a.(0); f a.(1); ...; f a.(Array.length a - 1) |]]. *)
val to_list: 'a array -> 'a list
+ (* [Array.to_list a] returns the list of all the elements of [a]. *)
val of_list: 'a list -> 'a array
+ (* [Array.of_list l] returns a fresh array containing the elements
+ of [l]. *)
+
+(*--*)
external unsafe_get: 'a array -> int -> 'a = "%array_unsafe_get"
external unsafe_set: 'a array -> int -> 'a -> unit = "%array_unsafe_set"
diff --git a/stdlib/char.mli b/stdlib/char.mli
index 7afa37bb4..6d7b53565 100644
--- a/stdlib/char.mli
+++ b/stdlib/char.mli
@@ -1,6 +1,16 @@
-(* Character operations *)
+(* Module [Char]: character operations *)
external code: char -> int = "%identity"
+ (* Return the ASCII code of the argument. *)
val chr: int -> char
+ (* Return the character with the given ASCII code.
+ Raise [Invalid_argument "char_of_int"] if the argument is
+ outside the range 0--255. *)
val escaped : char -> string
+ (* Return a string representing the given character,
+ with special characters escaped following the lexical conventions
+ of Caml Light. *)
+
+(*--*)
+
external unsafe_chr: int -> char = "%identity"
diff --git a/stdlib/filename.mli b/stdlib/filename.mli
index 4e45d3553..91363bde8 100644
--- a/stdlib/filename.mli
+++ b/stdlib/filename.mli
@@ -1,4 +1,4 @@
-(* Operations on file names *)
+(* Module [Filename]: operations on file names *)
val current_dir_name : string
(* The conventional name for the current directory
diff --git a/stdlib/format.mli b/stdlib/format.mli
index f2efe77c7..1425b4868 100644
--- a/stdlib/format.mli
+++ b/stdlib/format.mli
@@ -1,4 +1,4 @@
-(* Pretty printing *)
+(* Module [Format]: pretty printing *)
(* This module implements a pretty-printing facility to format text
within ``pretty-printing boxes''. The pretty-printer breaks lines
diff --git a/stdlib/gc.mli b/stdlib/gc.mli
index 614cda556..ea0ed5f1b 100644
--- a/stdlib/gc.mli
+++ b/stdlib/gc.mli
@@ -1,4 +1,4 @@
-(* Memory management control and statistics. *)
+(* Module [Gc]: memory management control and statistics *)
type stat = {
minor_words : int;
@@ -39,7 +39,7 @@ type stat = {
cannot be inserted in the free list, thus they are not available
for allocation.
-- The total amount of memory allocated by the program is (in words)
+ The total amount of memory allocated by the program is (in words)
[minor_words + major_words - promoted_words]. Multiply by
the word size (4 on a 32-bit machine, 8 on a 64-bit machine) to get
the number of bytes.
@@ -80,7 +80,7 @@ external set : control -> unit = "gc_set"
The normal usage is:
[
let r = Gc.get () in (* Get the current parameters. *)
- r.verbose <- true; (* Change some of them. *)
+ r.verbose <- true; (* Change some of them. *)
Gc.set r (* Set the new values. *)
]
*)
diff --git a/stdlib/hashtbl.mli b/stdlib/hashtbl.mli
index 1dedd6a1c..9bde6fed4 100644
--- a/stdlib/hashtbl.mli
+++ b/stdlib/hashtbl.mli
@@ -1,4 +1,4 @@
-(* Hash tables and hash functions *)
+(* Module [Hashtbl]: hash tables and hash functions *)
(* Hash tables are hashed association tables, with in-place modification. *)
@@ -6,7 +6,8 @@ type ('a, 'b) t
(* The type of hash tables from type ['a] to type ['b]. *)
val new : int -> ('a,'b) t
- (* [new n] creates a new, empty hash table, with initial size [n].
+ (* [Hashtbl.new n] creates a new, empty hash table,
+ with initial size [n].
The table grows as needed, so [n] is just an initial guess.
Better results are said to be achieved when [n] is a prime
number. *)
@@ -15,28 +16,29 @@ val clear : ('a, 'b) t -> unit
(* Empty a hash table. *)
val add : ('a, 'b) t -> 'a -> 'b -> unit
- (* [add tbl x y] adds a binding of [x] to [y] in table [tbl].
+ (* [Hashtbl.add tbl x y] adds a binding of [x] to [y] in table [tbl].
Previous bindings for [x] are not removed, but simply
hidden. That is, after performing [remove tbl x], the previous
binding for [x], if any, is restored.
(This is the semantics of association lists.) *)
val find : ('a, 'b) t -> 'a -> 'b
- (* [find tbl x] returns the current binding of [x] in [tbl],
+ (* [Hashtbl.find tbl x] returns the current binding of [x] in [tbl],
or raises [Not_found] if no such binding exists. *)
val find_all : ('a, 'b) t -> 'a -> 'b list
- (* [find_all tbl x] returns the list of all data associated with [x]
- in [tbl]. The current binding is returned first, then the previous
+ (* [Hashtbl.find_all tbl x] returns the list of all data
+ associated with [x] in [tbl].
+ The current binding is returned first, then the previous
bindings, in reverse order of introduction in the table. *)
val remove : ('a, 'b) t -> 'a -> unit
- (* [remove tbl x] removes the current binding of [x] in [tbl],
+ (* [Hashtbl.remove tbl x] removes the current binding of [x] in [tbl],
restoring the previous binding if it exists.
It does nothing if [x] is not bound in [tbl]. *)
val iter : ('a -> 'b -> 'c) -> ('a, 'b) t -> unit
- (* [iter f tbl] applies [f] to all bindings in table [tbl],
+ (* [Hashtbl.iter f tbl] applies [f] to all bindings in table [tbl],
discarding all the results.
[f] receives the key as first argument, and the associated val
as second argument. The order in which the bindings are passed to
@@ -46,14 +48,14 @@ val iter : ('a -> 'b -> 'c) -> ('a, 'b) t -> unit
(*** The polymorphic hash primitive *)
val hash : 'a -> int
- (* [hash x] associates a positive integer to any val of
+ (* [Hashtbl.hash x] associates a positive integer to any val of
any type. It is guaranteed that
if [x = y], then [hash x = hash y].
Moreover, [hash] always terminates, even on cyclic
structures. *)
external hash_param : int -> int -> 'a -> int = "hash_univ_param" "noalloc"
- (* [hash_param n m x] computes a hash val for [x], with the
+ (* [Hashtbl.hash_param n m x] computes a hash val for [x], with the
same properties as for [hash]. The two extra parameters [n] and
[m] give more precise control over hashing. Hashing performs a
depth-first, right-to-left traversal of the structure [x], stopping
diff --git a/stdlib/lexing.mli b/stdlib/lexing.mli
index 280c41bf1..2c4c53da1 100644
--- a/stdlib/lexing.mli
+++ b/stdlib/lexing.mli
@@ -1,4 +1,4 @@
-(* The run-time library for lexers generated by camllex *)
+(* Module [Lexing]: the run-time library for lexers generated by [camllex] *)
(*** Lexer buffers *)
diff --git a/stdlib/list.ml b/stdlib/list.ml
index b86ee453d..f761e138f 100644
--- a/stdlib/list.ml
+++ b/stdlib/list.ml
@@ -31,10 +31,6 @@ let rec map f = function
[] -> []
| a::l -> let r = f a in r :: map f l
-(* let rec map f = function
- [] -> []
- | a::l -> f a :: map f l *)
-
let rec iter f = function
[] -> ()
| a::l -> f a; iter f l
diff --git a/stdlib/list.mli b/stdlib/list.mli
index 56fba7b72..14cff7949 100644
--- a/stdlib/list.mli
+++ b/stdlib/list.mli
@@ -1,25 +1,102 @@
-(* List operations *)
+(* Module [List]: list operations *)
val length : 'a list -> int
+ (* Return the length (number of elements) of the given list. *)
val hd : 'a list -> 'a
+ (* Return the first element of the given list. Raise
+ [Failure "hd"] if the list is empty. *)
val tl : 'a list -> 'a list
+ (* Return the given list without its first element. Raise
+ [Failure "tl"] if the list is empty. *)
val nth : 'a list -> int -> 'a
+ (* Return the n-th element of the given list.
+ The first element (head of the list) is at position 0.
+ Raise [Failure "nth"] if the list is too short. *)
val rev : 'a list -> 'a list
+ (* List reversal. *)
val flatten : 'a list list -> 'a list
+ (* Catenate (flatten) a list of lists. *)
+
+(** Iterators *)
+
val iter : ('a -> 'b) -> 'a list -> unit
+ (* [List.iter f [a1; ...; an]] applies function [f] in turn to
+ [a1; ...; an], discarding all the results. It is equivalent to
+ [begin f a1; f a2; ...; f an; () end]. *)
val map : ('a -> 'b) -> 'a list -> 'b list
+ (* [List.map f [a1; ...; an]] applies function [f] to [a1, ..., an],
+ and builds the list [[f a1; ...; f an]]
+ with the results returned by [f]. *)
val fold_left : ('a -> 'b -> 'a) -> 'a -> 'b list -> 'a
+ (* [List.fold_left f a [b1; ...; bn]] is
+ [f (... (f (f a b1) b2) ...) bn]. *)
val fold_right : ('a -> 'b -> 'b) -> 'a list -> 'b -> 'b
-val map2 : ('a -> 'b -> 'c) -> 'a list -> 'b list -> 'c list
+ (* [List.fold_right f [a1; ...; an] b] is
+ [f a1 (f a2 (... (f an b) ...))]. *)
+
+(** Iterators on two lists *)
+
val iter2 : ('a -> 'b -> 'c) -> 'a list -> 'b list -> unit
+ (* [List.iter2 f [a1; ...; an] [b1; ...; bn]] calls in turn
+ [f a1 b1; ...; f an bn], discarding the results.
+ Raise [Invalid_argument] if the two lists have
+ different lengths. *)
+val map2 : ('a -> 'b -> 'c) -> 'a list -> 'b list -> 'c list
+ (* [List.map2 f [a1; ...; an] [b1; ...; bn]] is
+ [[f a1 b1; ...; f an bn]].
+ Raise [Invalid_argument] if the two lists have
+ different lengths. *)
val fold_left2 : ('a -> 'b -> 'c -> 'a) -> 'a -> 'b list -> 'c list -> 'a
+ (* [List.fold_left2 f a [b1; ...; bn] [c1; ...; cn]] is
+ [f (... (f (f a b1 c1) b2 c2) ...) bn cn].
+ Raise [Invalid_argument] if the two lists have
+ different lengths. *)
val fold_right2 : ('a -> 'b -> 'c -> 'c) -> 'a list -> 'b list -> 'c -> 'c
+ (* [List.fold_right2 f [a1; ...; an] [b1; ...; bn] c] is
+ [f a1 b1 (f a2 b2 (... (f an bn c) ...))].
+ Raise [Invalid_argument] if the two lists have
+ different lengths. *)
+
+(** List scanning *)
+
val for_all : ('a -> bool) -> 'a list -> bool
+ (* [for_all p [a1; ...; an]] checks if all elements of the list
+ satisfy the predicate [p]. That is, it returns
+ [(p a1) & (p a2) & ... & (p an)]. *)
val exists : ('a -> bool) -> 'a list -> bool
+ (* [exists p [a1; ...; an]] checks if at least one element of the list
+ satisfies the predicate [p]. That is, it returns
+ [(p a1) or (p a2) or ... or (p an)]. *)
val mem : 'a -> 'a list -> bool
+ (* [mem a l] is true if and only if [a] is equal
+ to an element of [l]. *)
+
+(** Association lists *)
+
val assoc : 'a -> ('a * 'b) list -> 'b
+ (* [assoc a l] returns the value associated with key [a] in the list of
+ pairs [l]. That is,
+ [assoc a [ ...; (a,b); ...] = b]
+ if [(a,b)] is the leftmost binding of [a] in list [l].
+ Raise [Not_found] if there is no value associated with [a] in the
+ list [l]. *)
val mem_assoc : 'a -> ('a * 'b) list -> bool
+ (* Same as [assoc], but simply return true if a binding exists,
+ and false if no bindings exist for the given key. *)
val assq : 'a -> ('a * 'b) list -> 'b
+ (* Same as [assoc], but use physical equality instead of structural
+ equality to compare keys. *)
+
+(** Lists of pairs *)
+
val split : ('a * 'b) list -> 'a list * 'b list
+ (* Transform a list of pairs into a pair of lists:
+ [split [(a1,b1); ...; (an,bn)]] is [([a1; ...; an], [b1; ...; bn])]
+ *)
val combine : 'a list -> 'b list -> ('a * 'b) list
+ (* Transform a pair of lists into a list of pairs:
+ [combine ([a1; ...; an], [b1; ...; bn])] is
+ [[(a1,b1); ...; (an,bn)]].
+ Raise [Invalid_argument] if the two lists
+ have different lengths. *)
diff --git a/stdlib/map.mli b/stdlib/map.mli
index 38e2e85e7..aaf21834b 100644
--- a/stdlib/map.mli
+++ b/stdlib/map.mli
@@ -1,20 +1,58 @@
-(* Maps over ordered types *)
+(* Module [Map]: association tables over ordered types *)
+
+(* This module implements applicative association tables, also known as
+ finite maps or dictionaries, given a total ordering function
+ over the keys.
+ All operations over maps are purely applicative (no side-effects).
+ The implementation uses balanced binary trees, and therefore searching
+ and insertion take time logarithmic in the size of the map. *)
module type OrderedType =
sig
type t
val compare: t -> t -> int
end
+ (* The input signature of the functor [Map.Make].
+ [t] is the type of the map keys.
+ [compare] is a total ordering function over the keys.
+ This is a two-argument function [f] such that
+ [f e1 e2] is zero if the keys [e1] and [e2] are equal,
+ [f e1 e2] is strictly negative if [e1] is smaller than [e2],
+ and [f e1 e2] is strictly positive if [e1] is greater than [e2].
+ Examples: a suitable ordering function for type [int]
+ is [prefix -]. You can also use the generic structural comparison
+ function [compare]. *)
module type S =
sig
type key
+ (* The type of the map keys. *)
type 'a t
+ (* The type of maps from type [key] to type ['a]. *)
val empty: 'a t
+ (* The empty map. *)
val add: key -> 'a -> 'a t -> 'a t
+ (* [add x y m] returns a map containing the same bindings as
+ [m], plus a binding of [x] to [y]. If [x] was already bound
+ in [m], its previous binding disappears. *)
val find: key -> 'a t -> 'a
+ (* [find x m] returns the current binding of [x] in [m],
+ or raises [Not_found] if no such binding exists. *)
val iter: (key -> 'a -> 'b) -> 'a t -> unit
+ (* [iter f m] applies [f] to all bindings in map [m],
+ discarding the results.
+ [f] receives the key as first argument, and the associated value
+ as second argument. The order in which the bindings are passed to
+ [f] is unspecified. Only current bindings are presented to [f]:
+ bindings hidden by more recent bindings are not passed to [f]. *)
val fold: (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
+ (* [fold f m a] computes [(f kN dN ... (f k1 d1 a)...)],
+ where [k1 ... kN] are the keys of all bindings in [m],
+ and [d1 ... dN] are the associated data.
+ The order in which the bindings are presented to [f] is
+ not specified. *)
end
module Make(Ord: OrderedType): (S with key = Ord.t)
+ (* Functor building an implementation of the map structure
+ given a totally ordered type. *)
diff --git a/stdlib/obj.mli b/stdlib/obj.mli
index 8fe21c7f6..602ea4b7c 100644
--- a/stdlib/obj.mli
+++ b/stdlib/obj.mli
@@ -1,4 +1,6 @@
-(* Operations on internal representations of values *)
+(* Module [Obj]: operations on internal representations of values *)
+
+(* Not for the casual user. *)
type t
diff --git a/stdlib/parsing.mli b/stdlib/parsing.mli
index c1c1fedad..62201b2c9 100644
--- a/stdlib/parsing.mli
+++ b/stdlib/parsing.mli
@@ -1,4 +1,4 @@
-(* The run-time library for parsers generated by camlyacc *)
+(* Module [Parsing]: the run-time library for parsers generated by [camlyacc]*)
val symbol_start : unit -> int
val symbol_end : unit -> int
@@ -10,7 +10,7 @@ val symbol_end : unit -> int
in a file is at position 0. *)
val rhs_start: int -> int
val rhs_end: int -> int
- (* Same as [symbol_start] and [symbol_end] above, but return then
+ (* Same as [symbol_start] and [symbol_end], but return then
position of the string matching the [n]th item on the
right-hand side of the rule, where [n] is the integer parameter
to [lhs_start] and [lhs_end]. [n] is 1 for the leftmost item. *)
@@ -22,7 +22,9 @@ val clear_parser : unit -> unit
programs. *)
exception Parse_error
- (* Raised when a parser encounters a syntax error. *)
+ (* Raised when a parser encounters a syntax error.
+ Can also be raised from the action part of a grammar rule,
+ to initiate error recovery. *)
(*--*)
diff --git a/stdlib/pervasives.ml b/stdlib/pervasives.ml
index 384cb905b..18b80e251 100644
--- a/stdlib/pervasives.ml
+++ b/stdlib/pervasives.ml
@@ -167,10 +167,10 @@ let output oc s ofs len =
external output_byte : out_channel -> int -> unit = "output_char"
external output_binary_int : out_channel -> int -> unit = "output_int"
external output_value : out_channel -> 'a -> unit = "output_value"
-external output_compact_value : out_channel -> 'a -> unit = "output_value"
+
external seek_out : out_channel -> int -> unit = "seek_out"
external pos_out : out_channel -> int = "pos_out"
-external size_out : out_channel -> int = "channel_size"
+external out_channel_length : out_channel -> int = "channel_size"
external close_out : out_channel -> unit = "close_out"
(* General input functions *)
diff --git a/stdlib/pervasives.mli b/stdlib/pervasives.mli
index 84e5f92d5..01c7ba174 100644
--- a/stdlib/pervasives.mli
+++ b/stdlib/pervasives.mli
@@ -1,82 +1,197 @@
-(* The initially opened module *)
-
-(* Predefined in the compiler *)
-
-(***
-type int
-type char
-type string
-type float
-type bool
-type unit = ()
-type exn
-type 'a array
-type 'a list = [] | :: of 'a * 'a list
-type ('a, 'b, 'c) format
-exception Out_of_memory
-exception Invalid_argument of string
-exception Failure of string
-exception Not_found
-exception Sys_error of string
-exception End_of_file
-exception Division_by_zero
-***)
-
-(* Exceptions *)
+(* Module [Pervasives]: the initially opened module *)
+
+(* This module provides the built-in types (numbers, booleans,
+ strings, exceptions, references, lists, arrays, input-output channels, ...)
+ and the basic operations over these types.
+
+ This module is automatically opened at the beginning of each compilation.
+ All components of this module can therefore be referred by their short
+ name, without prefixing them by [Pervasives]. *)
+
+(*** Predefined types *)
+
+(*- type int *)
+ (* The type of integer numbers. *)
+(*- type char *)
+ (* The type of characters. *)
+(*- type string *)
+ (* The type of character strings. *)
+(*- type float *)
+ (* The type of floating-point numbers. *)
+(*- type bool *)
+ (* The type of booleans (truth values). *)
+(*- type unit = () *)
+ (* The type of the unit value. *)
+(*- type exn *)
+ (* The type of exception values. *)
+(*- type 'a array *)
+ (* The type of arrays whose elements have type ['a]. *)
+(*- type 'a list = [] | :: of 'a * 'a list *)
+ (* The type of lists whose elements have type ['a]. *)
+type 'a option = None | Some of 'a
+ (* The type of optional values. *)
+(*- type ('a, 'b, 'c) format *)
+ (* The type of format strings. ['a] is the type of the parameters
+ of the format, ['c] is the result type for the [printf]-style
+ function, and ['b] is the type of the first argument given to
+ [%a] and [%t] printing functions (see module [Printf]). *)
-external raise : exn -> 'a = "%raise"
-val failwith: string -> 'a
-val invalid_arg: string -> 'a
+(*** Exceptions *)
+external raise : exn -> 'a = "%raise"
+ (* Raise the given exception value *)
+(*- exception Invalid_argument of string *)
+ (* Exception raised by library functions to signal that the given
+ arguments do not make sense. *)
+(*- exception Failure of string *)
+ (* Exception raised by library functions to signal that they are
+ undefined on the given arguments. *)
+(*- exception Not_found *)
+ (* Exception raised by search functions when the desired object
+ could not be found. *)
+(*- exception Out_of_memory *)
+ (* Exception raised by the garbage collector
+ when there is insufficient memory to complete the computation. *)
+(*- exception Sys_error of string *)
+ (* Exception raised by the input/output functions to report
+ an operating system error. *)
+(*- exception End_of_file *)
+ (* Exception raised by input functions to signal that the
+ end of file has been reached. *)
+(*- exception Division_by_zero *)
+ (* Exception raised by division and remainder operations
+ when their second argument is null. *)
exception Exit
+ (* This exception is not raised by any library function. It is
+ provided for use in your programs. *)
+
+val invalid_arg: string -> 'a
+ (* Raise exception [Invalid_argument] with the given string. *)
+val failwith: string -> 'a
+ (* Raise exception [Failure] with the given string. *)
-(* Comparisons *)
+(*** Comparisons *)
external (=) : 'a -> 'a -> bool = "%equal"
+ (* [e1 = e2] tests for structural equality of [e1] and [e2].
+ Mutable structures (e.g. references and arrays) are equal
+ if and only if their current contents are structurally equal,
+ even if the two mutable objects are not the same physical object.
+ Equality between functional values raises [Invalid_argument].
+ Equality between cyclic data structures may not terminate. *)
external (<>) : 'a -> 'a -> bool = "%notequal"
+ (* Negation of [prefix =]. *)
external (<) : 'a -> 'a -> bool = "%lessthan"
external (>) : 'a -> 'a -> bool = "%greaterthan"
external (<=) : 'a -> 'a -> bool = "%lessequal"
external (>=) : 'a -> 'a -> bool = "%greaterequal"
+ (* Structural ordering functions. These functions coincide with
+ the usual orderings over integer, string and floating-point
+ numbers, and extend them to a total ordering over all types.
+ The ordering is compatible with [prefix =]. As in the case
+ of [prefix =], mutable structures are compared by contents.
+ Comparison between functional values raises [Invalid_argument].
+ Comparison between cyclic structures may not terminate. *)
external compare: 'a -> 'a -> int = "compare" "noalloc"
+ (* [compare x y] returns [0] if [x=y], a negative integer if
+ [x<y], and a positive integer if [x>y]. The same restrictions
+ as for [=] apply. [compare] can be used as the comparison function
+ required by the [Set] and [Map] modules. *)
val min: 'a -> 'a -> 'a
+ (* Return the smaller of the two arguments. *)
val max: 'a -> 'a -> 'a
+ (* Return the greater of the two arguments. *)
external (==) : 'a -> 'a -> bool = "%eq"
+ (* [e1 == e2] tests for physical equality of [e1] and [e2].
+ On integers and characters, it is the same as structural
+ equality. On mutable structures, [e1 == e2] is true if and only if
+ physical modification of [e1] also affects [e2].
+ On non-mutable structures, the behavior of [prefix ==] is
+ implementation-dependent, except that [e1 == e2] implies
+ [e1 = e2]. *)
external (!=) : 'a -> 'a -> bool = "%noteq"
+ (* Negation of [prefix ==]. *)
-(* Boolean operations *)
+(*** Boolean operations *)
external not : bool -> bool = "%boolnot"
+ (* The boolean negation. *)
external (&) : bool -> bool -> bool = "%sequand"
+ (* The boolean ``and''. Evaluation is sequential, left-to-right:
+ in [e1 & e2], [e1] is eavaluated first, and if it returns [false],
+ [e2] is not evaluated at all. *)
external (or) : bool -> bool -> bool = "%sequor"
+ (* The boolean ``or''. Evaluation is sequential, left-to-right:
+ in [e1 or e2], [e1] is eavaluated first, and if it returns [true],
+ [e2] is not evaluated at all. *)
+
+(*** Integer arithmetic *)
-(* Integer operations *)
+(* Integers are 31 bits wide (or 63 bits on 64-bit processors).
+ All operations are taken modulo $2^{31}$ (or $2^{63}$).
+ They do not fail on overflow. *)
external (~-) : int -> int = "%negint"
+ (* Unary negation. You can also write [-e] instead of [~-e]. *)
external succ : int -> int = "%succint"
+ (* [succ x] is [x+1]. *)
external pred : int -> int = "%predint"
+ (* [pred x] is [x-1]. *)
external (+) : int -> int -> int = "%addint"
+ (* Integer addition. *)
external (-) : int -> int -> int = "%subint"
+ (* Integer subtraction. *)
external ( * ) : int -> int -> int = "%mulint"
+ (* Integer multiplication. *)
external (/) : int -> int -> int = "%divint"
external (mod) : int -> int -> int = "%modint"
+ (* Integer division and remainder.
+ Raise [Division_by_zero] if the second argument is 0.
+ If one of the arguments is negative, the result is
+ platform-dependent. *)
val abs : int -> int
+ (* Return the absolute value of the argument. *)
+
+(** Bitwise operations *)
+
external (land) : int -> int -> int = "%andint"
+ (* Bitwise logical and. *)
external (lor) : int -> int -> int = "%orint"
+ (* Bitwise logical or. *)
external (lxor) : int -> int -> int = "%xorint"
+ (* Bitwise logical exclusive or. *)
val lnot: int -> int
+ (* Bitwise logical negation. *)
external (lsl) : int -> int -> int = "%lslint"
+ (* [n lsl m] shifts [n] to the left by [m] bits. *)
external (lsr) : int -> int -> int = "%lsrint"
+ (* [n lsr m] shifts [n] to the right by [m] bits.
+ This is a logical shift: zeroes are inserted regardless of
+ the sign of [n].*)
external (asr) : int -> int -> int = "%asrint"
+ (* [n asr m] shifts [n] to the right by [m] bits.
+ This is an arithmetic shift: the sign bit of [n] is replicated. *)
-(* Floating-point operations *)
+(*** Floating-point arithmetic *)
+
+(* On most platforms, Caml's floating-point numbers follow the
+ IEEE 754 standard, using double precision (64 bits) numbers.
+ Floating-point operations do not fail on overflow or underflow,
+ but return denormal numbers. *)
external (~-.) : float -> float = "%negfloat"
+ (* Unary negation. You can also write [-.e] instead of [~-.e]. *)
external (+.) : float -> float -> float = "%addfloat"
+ (* Floating-point addition *)
external (-.) : float -> float -> float = "%subfloat"
+ (* Floating-point subtraction *)
external ( *. ) : float -> float -> float = "%mulfloat"
+ (* Floating-point multiplication *)
external (/.) : float -> float -> float = "%divfloat"
+ (* Floating-point division. Raise [Division_by_zero] if second
+ argument is null. *)
external ( ** ) : float -> float -> float = "power_float" "pow" "float"
+ (* Exponentiation *)
external exp : float -> float = "exp_float" "exp" "float"
external log : float -> float = "log_float" "log" "float"
external sqrt : float -> float = "sqrt_float" "sqrt" "float"
@@ -87,118 +202,311 @@ external asin : float -> float = "asin_float" "asin" "float"
external acos : float -> float = "acos_float" "acos" "float"
external atan : float -> float = "atan_float" "atan" "float"
external atan2 : float -> float -> float = "atan2_float" "atan2" "float"
+ (* Usual transcendental functions on floating-point numbers. *)
val abs_float : float -> float
+ (* Return the absolute value of the argument. *)
external float : int -> float = "%floatofint"
+ (* Convert an integer to floating-point. *)
external truncate : float -> int = "%intoffloat"
+ (* Truncate the given floating-point number to an integer.
+ The result is unspecified if it falls outside the
+ range of representable integers. *)
-(* String operations -- more in module String *)
-
-val (^) : string -> string -> string
+(*** String operations *)
-(* Pair operations *)
+(* More string operations are provided in module [String]. *)
-external fst : 'a * 'b -> 'a = "%field0"
-external snd : 'a * 'b -> 'b = "%field1"
+val (^) : string -> string -> string
+ (* String concatenation. *)
-(* String conversion functions *)
+(*** String conversion functions *)
val string_of_bool : bool -> string
+ (* Return the string representation of a boolean. *)
val string_of_int : int -> string
+ (* Return the string representation of an integer, in decimal. *)
external int_of_string : string -> int = "int_of_string"
+ (* Convert the given string to an integer.
+ The string is read in decimal (by default) or in hexadecimal,
+ octal or binary if the string begins with [0x], [0o] or [0b]
+ respectively.
+ Raise [Failure "int_of_string"] if the given string is not
+ a valid representation of an integer. *)
val string_of_float : float -> string
+ (* Return the string representation of a floating-point number. *)
external float_of_string : string -> float = "float_of_string"
+ (* Convert the given string to a float.
+ The result is unspecified if the given string is not
+ a valid representation of a float. *)
+
+(*** Pair operations *)
+
+external fst : 'a * 'b -> 'a = "%field0"
+ (* Return the first component of a pair. *)
+external snd : 'a * 'b -> 'b = "%field1"
+ (* Return the second component of a pair. *)
-(* List operations -- more in module List *)
+(*** List operations *)
+
+(* More list operations are provided in module [List]. *)
val (@) : 'a list -> 'a list -> 'a list
+ (* List concatenation. *)
-(* I/O operations *)
+(*** Input/output *)
type in_channel
type out_channel
+ (* The types of input channels and output channels. *)
val stdin : in_channel
val stdout : out_channel
val stderr : out_channel
+ (* The standard input, standard output, and standard error output
+ for the process. *)
-(* Output functions on standard output *)
+(** Output functions on standard output *)
val print_char : char -> unit
+ (* Print a character on standard output. *)
val print_string : string -> unit
+ (* Print a string on standard output. *)
val print_int : int -> unit
+ (* Print an integer, in decimal, on standard output. *)
val print_float : float -> unit
+ (* Print a floating-point number, in decimal, on standard output. *)
val print_endline : string -> unit
+ (* Print a string, followed by a newline character, on
+ standard output. *)
val print_newline : unit -> unit
+ (* Print a newline character on standard output, and flush
+ standard output. This can be used to simulate line
+ buffering of standard output. *)
-(* Output functions on standard error *)
+(** Output functions on standard error *)
val prerr_char : char -> unit
+ (* Print a character on standard error. *)
val prerr_string : string -> unit
+ (* Print a string on standard error. *)
val prerr_int : int -> unit
+ (* Print an integer, in decimal, on standard error. *)
val prerr_float : float -> unit
+ (* Print a floating-point number, in decimal, on standard error. *)
val prerr_endline : string -> unit
+ (* Print a string, followed by a newline character on standard error
+ and flush standard error. *)
val prerr_newline : unit -> unit
+ (* Print a newline character on standard error, and flush
+ standard error. *)
-(* Input functions on standard input *)
+(** Input functions on standard input *)
val read_line : unit -> string
+ (* Flush standard output, then read characters from standard input
+ until a newline character is encountered. Return the string of
+ all characters read, without the newline character at the end. *)
val read_int : unit -> int
+ (* Flush standard output, then read one line from standard input
+ and convert it to an integer. Raise [Failure "int_of_string"]
+ if the line read is not a valid representation of an integer. *)
val read_float : unit -> float
+ (* Flush standard output, then read one line from standard input
+ and convert it to a floating-point number.
+ The result is unspecified if the line read is not a valid
+ representation of a floating-point number. *)
-(* General output functions *)
+(** General output functions *)
type open_flag =
Open_rdonly | Open_wronly | Open_rdwr
| Open_append | Open_creat | Open_trunc | Open_excl
| Open_binary | Open_text
-
+ (* Opening modes for [open_out_gen] and [open_in_gen].
+- [Open_rdonly]: open for reading.
+- [Open_wronly]: open for writing.
+- [Open_rdwr]: open for reading and writing.
+- [Open_append]: open for appending.
+- [Open_creat]: create the file if it does not exist.
+- [Open_trunc]: empty the file if it already exists.
+- [Open_excl]: fail if the file already exists.
+- [Open_binary]: open in binary mode (no conversion).
+- [Open_text]: open in text mode (may perform conversions). *)
+
val open_out : string -> out_channel
+ (* Open the named file for writing, and return a new output channel
+ on that file, positionned at the beginning of the file. The
+ file is truncated to zero length if it already exists. It
+ is created if it does not already exists.
+ Raise [Sys_error] if the file could not be opened. *)
val open_out_bin : string -> out_channel
+ (* Same as [open_out], but the file is opened in binary mode,
+ so that no translation takes place during writes. On operating
+ systems that do not distinguish between text mode and binary
+ mode, this function behaves like [open_out]. *)
val open_out_gen : open_flag list -> int -> string -> out_channel
+ (* [open_out_gen mode rights filename] opens the file named
+ [filename] for writing, as above. The extra argument [mode]
+ specify the opening mode. The extra argument [rights] specifies
+ the file permissions, in case the file must be created.
+ [open_out] and [open_out_bin] are special cases of this function. *)
external flush : out_channel -> unit = "flush"
+ (* Flush the buffer associated with the given output channel,
+ performing all pending writes on that channel.
+ Interactive programs must be careful about flushing standard
+ output and standard error at the right time. *)
external output_char : out_channel -> char -> unit = "output_char"
+ (* Write the character on the given output channel. *)
val output_string : out_channel -> string -> unit
+ (* Write the string on the given output channel. *)
val output : out_channel -> string -> int -> int -> unit
+ (* [output chan buff ofs len] writes [len] characters from string
+ [buff], starting at offset [ofs], to the output channel [chan].
+ Raise [Invalid_argument "output"] if [ofs] and [len] do not
+ designate a valid substring of [buff]. *)
external output_byte : out_channel -> int -> unit = "output_char"
+ (* Write one 8-bit integer (as the single character with that code)
+ on the given output channel. The given integer is taken modulo
+ 256. *)
external output_binary_int : out_channel -> int -> unit = "output_int"
+ (* Write one integer in binary format on the given output channel.
+ The only reliable way to read it back is through the
+ [input_binary_int] function. The format is compatible across
+ all machines for a given version of Caml Light. *)
external output_value : out_channel -> 'a -> unit = "output_value"
-external output_compact_value : out_channel -> 'a -> unit = "output_value"
+ (* Write the representation of a structured value of any type
+ to a channel. Circularities and sharing inside the value
+ are detected and preserved. The object can be read back,
+ by the function [input_value]. The format is compatible across
+ all machines for a given version of Caml Light. *)
external seek_out : out_channel -> int -> unit = "seek_out"
+ (* [seek_out chan pos] sets the current writing position to [pos]
+ for channel [chan]. This works only for regular files. On
+ files of other kinds (such as terminals, pipes and sockets),
+ the behavior is unspecified. *)
external pos_out : out_channel -> int = "pos_out"
-external size_out : out_channel -> int = "channel_size"
+ (* Return the current writing position for the given channel. *)
+external out_channel_length : out_channel -> int = "channel_size"
+ (* Return the total length (number of characters) of the
+ given channel. This works only for regular files. On files of
+ other kinds, the result is meaningless. *)
external close_out : out_channel -> unit = "close_out"
+ (* Close the given channel, flushing all buffered write operations.
+ The behavior is unspecified if any of the functions above is
+ called on a closed channel. *)
+
+(** General input functions *)
-(* General input functions *)
val open_in : string -> in_channel
+ (* Open the named file for reading, and return a new input channel
+ on that file, positionned at the beginning of the file.
+ Raise [Sys_error] if the file could not be opened. *)
val open_in_bin : string -> in_channel
+ (* Same as [open_in], but the file is opened in binary mode,
+ so that no translation takes place during reads. On operating
+ systems that do not distinguish between text mode and binary
+ mode, this function behaves like [open_in]. *)
val open_in_gen : open_flag list -> int -> string -> in_channel
+ (* [open_in_gen mode rights filename] opens the file named
+ [filename] for reading, as above. The extra arguments
+ [mode] and [rights] specify the opening mode and file permissions.
+ [open_in] and [open_in_bin] are special cases of this function. *)
external input_char : in_channel -> char = "input_char"
+ (* Read one character from the given input channel.
+ Raise [End_of_file] if there are no more characters to read. *)
val input_line : in_channel -> string
+ (* Read characters from the given input channel, until a
+ newline character is encountered. Return the string of
+ all characters read, without the newline character at the end.
+ Raise [End_of_file] if the end of the file is reached
+ at the beginning of line. *)
val input : in_channel -> string -> int -> int -> int
+ (* [input chan buff ofs len] attempts to read [len] characters
+ from channel [chan], storing them in string [buff], starting at
+ character number [ofs]. It returns the actual number of characters
+ read, between 0 and [len] (inclusive).
+ A return value of 0 means that the end of file was reached.
+ A return value between 0 and [len] exclusive means that
+ no more characters were available at that time; [input] must be
+ called again to read the remaining characters, if desired.
+ Exception [Invalid_argument "input"] is raised if [ofs] and [len]
+ do not designate a valid substring of [buff]. *)
val really_input : in_channel -> string -> int -> int -> unit
+ (* [really_input chan buff ofs len] reads [len] characters
+ from channel [chan], storing them in string [buff], starting at
+ character number [ofs]. Raise [End_of_file] if
+ the end of file is reached before [len] characters have been read.
+ Raise [Invalid_argument "really_input"] if
+ [ofs] and [len] do not designate a valid substring of [buff]. *)
external input_byte : in_channel -> int = "input_char"
+ (* Same as [input_char], but return the 8-bit integer representing
+ the character.
+ Raise [End_of_file] if an end of file was reached. *)
external input_binary_int : in_channel -> int = "input_int"
+ (* Read an integer encoded in binary format from the given input
+ channel. See [output_binary_int].
+ Raise [End_of_file] if an end of file was reached while reading the
+ integer. *)
external input_value : in_channel -> 'a = "input_value"
+ (* Read the representation of a structured value, as produced
+ by [output_value] or [output_compact_value], and return
+ the corresponding value.
+ This is not type-safe. The type of the returned object is
+ not ['a] properly speaking: the returned object has one
+ unique type, which cannot be determined at compile-time.
+ The programmer should explicitly give the expected type of the
+ returned value, using the following syntax:
+ [(input_value chan : type)].
+ The behavior is unspecified if the object in the file does not
+ belong to the given type. *)
external seek_in : in_channel -> int -> unit = "seek_in"
+ (* [seek_in chan pos] sets the current reading position to [pos]
+ for channel [chan]. This works only for regular files. On
+ files of other kinds, the behavior is unspecified. *)
external pos_in : in_channel -> int = "pos_in"
+ (* Return the current reading position for the given channel. *)
external in_channel_length : in_channel -> int = "channel_size"
+ (* Return the total length (number of characters) of the
+ given channel. This works only for regular files. On files of
+ other kinds, the result is meaningless. *)
external close_in : in_channel -> unit = "close_in"
+ (* Close the given channel. Anything can happen if any of the
+ functions above is called on a closed channel. *)
-(* References *)
+(*** References *)
type 'a ref = { mutable contents: 'a }
+ (* The type of references (mutable indirection cells) containing
+ a value of type ['a]. *)
external ref: 'a -> 'a ref = "%makeblock"
+ (* Return a fresh reference containing the given value. *)
external (!): 'a ref -> 'a = "%field0"
+ (* [!r] returns the current contents of reference [r].
+ Could be defined as [fun r -> r.contents]. *)
external (:=): 'a ref -> 'a -> unit = "%setfield0"
+ (* [r := a] stores the value of [a] in reference [r].
+ Could be defined as [fun r v -> r.contents <- v]. *)
external incr: int ref -> unit = "%incr"
+ (* Increment the integer contained in the given reference.
+ Could be defined as [fun r -> r := succ !r]. *)
external decr: int ref -> unit = "%decr"
+ (* Decrement the integer contained in the given reference.
+ Could be defined as [fun r -> r := pred !r]. *)
-(* Miscellaneous *)
+(*** Program termination *)
val exit : int -> 'a
-
-type 'a option = None | Some of 'a
-
-(**** For system use, not for the casual user ****)
+ (* Flush all pending writes on [stdout] and [stderr],
+ and terminate the process, returning the given status code
+ to the operating system (usually 0 to indicate no errors,
+ and a small positive integer to indicate failure.)
+ This function should be called at
+ the end of all standalone programs that output results on
+ [stdout] or [stderr]; otherwise, the program may appear
+ to produce no output, or its output may be truncated. *)
+
+(*--*)
+
+(*** For system use only, not for the casual user *)
val unsafe_really_input: in_channel -> string -> int -> int -> unit
diff --git a/stdlib/printexc.mli b/stdlib/printexc.mli
index 0b56bd2a8..864f1ac84 100644
--- a/stdlib/printexc.mli
+++ b/stdlib/printexc.mli
@@ -1,4 +1,4 @@
-(* A catch-all exception handler *)
+(* Module [Printexc]: a catch-all exception handler *)
val catch: ('a -> 'b) -> 'a -> 'b
(* [Printexc.catch fn x] applies [fn] to [x] and returns the result.
@@ -6,8 +6,8 @@ val catch: ('a -> 'b) -> 'a -> 'b
name of the exception is printed on standard error output,
and the programs aborts with exit code 2.
Typical use is [Printexc.catch main ()], where [main], with type
- [unit->unit], is the entry point of a standalone program, to catch
- and print stray exceptions. *)
+ [unit->unit], is the entry point of a standalone program.
+ This catches and reports any exception that escapes the program. *)
val print: ('a -> 'b) -> 'a -> 'b
(* Same as [catch], but re-raise the stray exception after
diff --git a/stdlib/printf.mli b/stdlib/printf.mli
index c139d504d..2a2251357 100644
--- a/stdlib/printf.mli
+++ b/stdlib/printf.mli
@@ -1,4 +1,4 @@
-(* Formatting printing functions *)
+(* Module [Printf]: formatting printing functions *)
val fprintf: out_channel -> ('a, out_channel, unit) format -> 'a
(* [fprintf outchan format arg1 ... argN] formats the arguments
diff --git a/stdlib/queue.mli b/stdlib/queue.mli
index 297e81afa..45fcb2c1e 100644
--- a/stdlib/queue.mli
+++ b/stdlib/queue.mli
@@ -1,4 +1,4 @@
-(* Queues *)
+(* Module [Queues]: queues *)
(* This module implements queues (FIFOs), with in-place modification. *)
@@ -23,6 +23,6 @@ val clear : 'a t -> unit
val length: 'a t -> int
(* Return the number of elements in a queue. *)
val iter: ('a -> 'b) -> 'a t -> unit
- (* [iter f q] applies [f] in turn to all elements of [q], from the
- least recently entered to the most recently entered.
+ (* [Queue.iter f q] applies [f] in turn to all elements of [q],
+ from the least recently entered to the most recently entered.
The queue itself is unchanged. *)
diff --git a/stdlib/set.mli b/stdlib/set.mli
index f88480b3c..53debbca2 100644
--- a/stdlib/set.mli
+++ b/stdlib/set.mli
@@ -1,30 +1,76 @@
-(* Sets over ordered types *)
+(* Module [Set]: sets over ordered types *)
+
+(* This module implements the set data structure, given a total ordering
+ function over the set elements. All operations over sets
+ are purely applicative (no side-effects).
+ The implementation uses balanced binary trees, and is therefore
+ reasonably efficient: insertion and membership take time
+ logarithmic in the size of the set, for instance. *)
module type OrderedType =
sig
type t
val compare: t -> t -> int
end
+ (* The input signature of the functor [Set.Make].
+ [t] is the type of the set elements.
+ [compare] is a total ordering function over the set elements.
+ This is a two-argument function [f] such that
+ [f e1 e2] is zero if the elements [e1] and [e2] are equal,
+ [f e1 e2] is strictly negative if [e1] is smaller than [e2],
+ and [f e1 e2] is strictly positive if [e1] is greater than [e2].
+ Examples: a suitable ordering function for type [int]
+ is [prefix -]. You can also use the generic structural comparison
+ function [compare]. *)
module type S =
sig
type elt
+ (* The type of the set elements. *)
type t
+ (* The type of sets. *)
val empty: t
+ (* The empty set. *)
val is_empty: t -> bool
+ (* Test whether a set is empty or not. *)
val mem: elt -> t -> bool
+ (* [mem x s] tests whether [x] belongs to the set [s]. *)
val add: elt -> t -> t
+ (* [add x s] returns a set containing all elements of [s],
+ plus [x]. If [x] was already in [s], [s] is returned unchanged. *)
val remove: elt -> t -> t
+ (* [remove x s] returns a set containing all elements of [s],
+ except [x]. If [x] was not in [s], [s] is returned unchanged. *)
val union: t -> t -> t
val inter: t -> t -> t
val diff: t -> t -> t
+ (* Union, intersection and set difference. *)
val compare: t -> t -> int
+ (* Total ordering between sets. Can be used as the ordering function
+ for doing sets of sets. *)
val equal: t -> t -> bool
+ (* [equal s1 s2] tests whether the sets [s1] and [s2] are
+ equal, that is, contain the same elements. *)
val iter: (elt -> 'a) -> t -> unit
+ (* [iter f s] applies [f] in turn to all elements of [s], and
+ discards the results. The elements of [s] are presented to [f]
+ in a non-specified order. *)
val fold: (elt -> 'a -> 'a) -> t -> 'a -> 'a
+ (* [fold f s a] computes [(f xN ... (f x2 (f x1 a))...)],
+ where [x1 ... xN] are the elements of [s].
+ The order in which elements of [s] are presented to [f] is
+ not specified. *)
val cardinal: t -> int
+ (* Return the number of elements of a set. *)
val elements: t -> elt list
+ (* Return the list of all elements of the given set.
+ The elements appear in the list in some non-specified order. *)
val choose: t -> elt
+ (* Return one element of the given set, or raise [Not_found] if
+ the set is empty. Which element is chosen is not specified,
+ but equal elements will be chosen for equal sets. *)
end
module Make(Ord: OrderedType): (S with elt = Ord.t)
+ (* Functor building an implementation of the set structure
+ given a totally ordered type. *)
diff --git a/stdlib/sort.mli b/stdlib/sort.mli
index 545a0fad7..1378d0720 100644
--- a/stdlib/sort.mli
+++ b/stdlib/sort.mli
@@ -1,4 +1,4 @@
-(* Sorting and merging lists *)
+(* Module [Sort]: sorting and merging lists *)
val list : ('a -> 'a -> bool) -> 'a list -> 'a list
(* Sort a list in increasing order according to an ordering predicate.
diff --git a/stdlib/stack.mli b/stdlib/stack.mli
index a1133edcc..03463a1ec 100644
--- a/stdlib/stack.mli
+++ b/stdlib/stack.mli
@@ -1,4 +1,4 @@
-(* Stacks *)
+(* Module [Stack]: stacks *)
(* This modl implements stacks (LIFOs), with in-place modification. *)
@@ -20,6 +20,6 @@ val clear : 'a t -> unit
val length: 'a t -> int
(* Return the number of elements in a stack. *)
val iter: ('a -> 'b) -> 'a t -> unit
- (* [iter f s] applies [f] in turn to all elements of [s], from the
- element at the top of the stack to the element at the
+ (* [Stack.iter f s] applies [f] in turn to all elements of [s],
+ from the element at the top of the stack to the element at the
bottom of the stack. The stack itself is unchanged. *)
diff --git a/stdlib/string.mli b/stdlib/string.mli
index 164aef487..fe1b2497c 100644
--- a/stdlib/string.mli
+++ b/stdlib/string.mli
@@ -1,21 +1,62 @@
-(* String operations *)
+(* Module [String]: string operations *)
external length : string -> int = "%string_length"
+ (* Return the length (number of characters) of the given string. *)
external get : string -> int -> char = "%string_safe_get"
+ (* [String.get s n] returns character number [n] in string [s].
+ The first character is character number 0.
+ The last character is character number [String.length s - 1].
+ Raise [Invalid_argument] if [n] is ouside the range
+ 0 to [(String.length s - 1)].
+ You can also write [s.[n]] instead of [String.get s n]. *)
external set : string -> int -> char -> unit = "%string_safe_set"
+ (* [String.set s n c] modifies string [s] in place,
+ replacing the character number [n] by [c].
+ Raise [Invalid_argument] if [n] is ouside the range
+ 0 to [(String.length s - 1)].
+ You can also write [s.[n] <- c] instead of [String.set s n c]. *)
external create : int -> string = "create_string"
+ (* [String.create n] returns a fresh string of length [n].
+ The string initially contains arbitrary characters. *)
val make : int -> char -> string
+ (* [String.make n c] returns a fresh string of length [n],
+ filled with the character [c]. *)
val copy : string -> string
+ (* Return a copy of the given string. *)
val sub : string -> int -> int -> string
-
+ (* [String.sub s start len] returns a fresh string of length [len],
+ containing the characters number [start] to [start + len - 1]
+ of string [s].
+ Raise [Invalid_argument] if [start] and [len] do not
+ designate a valid substring of [s]; that is, if [start < 0],
+ or [len < 0], or [start + len > String.length s]. *)
val fill : string -> int -> int -> char -> unit
+ (* [fill_string s start len c] modifies string [s] in place,
+ replacing the characters number [start] to [start + len - 1]
+ by [c].
+ Raise [Invalid_argument] if [start] and [len] do not
+ designate a valid substring of [s]. *)
val blit : string -> int -> string -> int -> int -> unit
+ (* [blit_string s1 o1 s2 o2 len] copies [len] characters
+ from string [s1], starting at character number [o1], to string [s2],
+ starting at character number [o2]. It works correctly even if
+ [s1] and [s2] are the same string,
+ and the source and destination chunks overlap.
+ Raise [Invalid_argument] if [o1] and [len] do not
+ designate a valid substring of [s1], or if [o2] and [len] do not
+ designate a valid substring of [s2]. *)
val concat : string -> string list -> string
+ (* Catenate a list of strings. *)
val escaped: string -> string
+ (* Return a copy of the argument, with special characters represented
+ by escape sequences, following the lexical conventions of
+ Caml Light. *)
+
+(*--*)
external unsafe_get : string -> int -> char = "%string_unsafe_get"
external unsafe_set : string -> int -> char -> unit = "%string_unsafe_set"
diff --git a/stdlib/sys.mli b/stdlib/sys.mli
index 0466ba591..3fb694d2b 100644
--- a/stdlib/sys.mli
+++ b/stdlib/sys.mli
@@ -1,39 +1,65 @@
-(* System interface *)
+(* Module [Sys]: system interface *)
val argv: string array
+ (* The command line arguments given to the process.
+ The first element is the command name used to invoke the program.
+ The following elements are the arguments given to the program. *)
external file_exists: string -> bool = "sys_file_exists"
+ (* Test if a file with the given name exists. *)
external remove: string -> unit = "sys_remove"
+ (* Remove the given file name from the file system. *)
external getenv: string -> string = "sys_getenv"
+ (* Return the value associated to a variable in the process
+ environment. Raise [Not_found] if the variable is unbound. *)
external command: string -> int = "sys_system_command"
+ (* Execute the given shell command and return its exit code. *)
external chdir: string -> unit = "sys_chdir"
+ (* Change the current working directory of the process. *)
+
+(*** Signal handling *)
type signal_behavior =
Signal_default
| Signal_ignore
| Signal_handle of (int -> unit)
+ (* What to do when receiving a signal:
+- [Signal_default]: take the default behavior
+- [Signal_ignore]: ignore the signal
+- [Signal_handle f]: call function [f], giving it the signal
+ number as argument. *)
external signal: int -> signal_behavior -> unit = "install_signal_handler"
+ (* Set the behavior of the system on receipt of a given signal.
+ The first argument is the signal number. *)
-val sigabrt: int
-val sigalrm: int
-val sigfpe: int
-val sighup: int
-val sigill: int
-val sigint: int
-val sigkill: int
-val sigpipe: int
-val sigquit: int
-val sigsegv: int
-val sigterm: int
-val sigusr1: int
-val sigusr2: int
-val sigchld: int
-val sigcont: int
-val sigstop: int
-val sigtstp: int
-val sigttin: int
-val sigttou: int
+val sigabrt: int (* Abnormal termination *)
+val sigalrm: int (* Timeout *)
+val sigfpe: int (* Arithmetic exception *)
+val sighup: int (* Hangup on controlling terminal *)
+val sigill: int (* Invalid hardware instruction *)
+val sigint: int (* Interactive interrupt (ctrl-C) *)
+val sigkill: int (* Termination (cannot be ignored) *)
+val sigpipe: int (* Broken pipe *)
+val sigquit: int (* Interactive termination *)
+val sigsegv: int (* Invalid memory reference *)
+val sigterm: int (* Termination *)
+val sigusr1: int (* Application-defined signal 1 *)
+val sigusr2: int (* Application-defined signal 2 *)
+val sigchld: int (* Child process terminated *)
+val sigcont: int (* Continue *)
+val sigstop: int (* Stop *)
+val sigtstp: int (* Interactive stop *)
+val sigttin: int (* Terminal read from background process *)
+val sigttou: int (* Terminal write from background process *)
+ (* Signal numbers for the standard POSIX signals. *)
exception Break
+ (* Exception raised on interactive interrupt if [catch_break]
+ is on. *)
val catch_break: bool -> unit
+ (* [catch_break] governs whether interactive interrupt (ctrl-C)
+ terminates the program or raises the [Break] exception.
+ Call [catch_break true] to enable raising [Break],
+ and [catch_break false] to let the system
+ terminate the program on user interrupt. *)