commentaires après
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4082 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
8cd61ac055
commit
966c128bc9
|
@ -37,18 +37,21 @@
|
|||
two arguments)
|
||||
*)
|
||||
|
||||
(** The concrete type describing the behavior associated
|
||||
with a keyword. *)
|
||||
type spec =
|
||||
| Unit of (unit -> unit) (** Call the function with unit argument *)
|
||||
Unit of (unit -> unit) (** Call the function with unit argument *)
|
||||
| Set of bool ref (** Set the reference to true *)
|
||||
| Clear of bool ref (** Set the reference to false *)
|
||||
| String of (string -> unit) (** Call the function with a string argument *)
|
||||
| Int of (int -> unit) (** Call the function with an int argument *)
|
||||
| Float of (float -> unit) (** Call the function with a float argument *)
|
||||
| Rest of (string -> unit) (** Stop interpreting keywords and call the
|
||||
function with each remaining argument *)
|
||||
| Rest of (string -> unit) (** Stop interpreting keywords and call the
|
||||
function with each remaining argument *)
|
||||
|
||||
(** The concrete type describing the behavior associated
|
||||
with a keyword. *)
|
||||
|
||||
val parse :
|
||||
(string * spec * string) list -> (string -> unit) -> string -> unit
|
||||
(** [Arg.parse speclist anonfun usage_msg] parses the command line.
|
||||
[speclist] is a list of triples [(key, spec, doc)].
|
||||
[key] is the option keyword, it must start with a ['-'] character.
|
||||
|
@ -73,19 +76,17 @@ type spec =
|
|||
the program. You can override this behaviour by specifying your
|
||||
own [-help] and [--help] options in [speclist].
|
||||
*)
|
||||
val parse : (string * spec * string) list ->
|
||||
(string -> unit) -> string -> unit
|
||||
|
||||
exception Bad of string
|
||||
(** Functions in [spec] or [anonfun] can raise [Arg.Bad] with an error
|
||||
message to reject invalid arguments. *)
|
||||
exception Bad of string
|
||||
|
||||
val usage : (string * spec * string) list -> string -> unit
|
||||
(** [Arg.usage speclist usage_msg] prints an error message including
|
||||
the list of valid options. This is the same message that
|
||||
{!Arg.parse} prints in case of error.
|
||||
[speclist] and [usage_msg] are the same as for [Arg.parse]. *)
|
||||
val usage : (string * spec * string) list -> string -> unit
|
||||
|
||||
val current : int ref
|
||||
(** Position (in {!Sys.argv}) of the argument being processed. You can
|
||||
change this value, e.g. to force {!Arg.parse} to skip some arguments.*)
|
||||
val current : int ref;;
|
||||
|
|
|
@ -14,9 +14,10 @@
|
|||
|
||||
(** Array operations. *)
|
||||
|
||||
(** Return the length (number of elements) of the given array. *)
|
||||
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].
|
||||
|
@ -24,16 +25,16 @@ external length : 'a array -> int = "%array_length"
|
|||
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 [Array.get a n]. *)
|
||||
external get: 'a array -> int -> 'a = "%array_safe_get"
|
||||
|
||||
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 [Array.set a n x]. *)
|
||||
external set: 'a array -> int -> 'a -> unit = "%array_safe_set"
|
||||
|
||||
external make : int -> 'a -> 'a array = "make_vect"
|
||||
(** [Array.make n x] returns a fresh array of length [n],
|
||||
initialized with [x].
|
||||
All the elements of this new array are initially
|
||||
|
@ -45,17 +46,17 @@ external set: 'a array -> int -> 'a -> unit = "%array_safe_set"
|
|||
Raise [Invalid_argument] if [n < 0] or [n > Sys.max_array_length].
|
||||
If the value of [x] is a floating-point number, then the maximum
|
||||
size is only [Sys.max_array_length / 2].*)
|
||||
external make: int -> 'a -> 'a array = "make_vect"
|
||||
|
||||
external create : int -> 'a -> 'a array = "make_vect"
|
||||
(** @deprecated [Array.create] is an alias for {!Array.make}. *)
|
||||
external create: int -> 'a -> 'a array = "make_vect"
|
||||
|
||||
val init : int -> (int -> 'a) -> 'a array
|
||||
(** [Array.init n f] returns a fresh array of length [n],
|
||||
with element number [i] initialized to the result of [f i].
|
||||
In other terms, [Array.init n f] tabulates the results of [f]
|
||||
applied to the integers [0] to [n-1]. *)
|
||||
val init: int -> (int -> 'a) -> 'a array
|
||||
|
||||
val make_matrix : int -> int -> 'a -> 'a array array
|
||||
(** [Array.make_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
|
||||
|
@ -67,18 +68,18 @@ val init: int -> (int -> 'a) -> 'a array
|
|||
greater than [Sys.max_array_length].
|
||||
If the value of [e] is a floating-point number, then the maximum
|
||||
size is only [Sys.max_array_length / 2]. *)
|
||||
val make_matrix: int -> int -> 'a -> 'a array array
|
||||
|
||||
val create_matrix : int -> int -> 'a -> 'a array array
|
||||
(** @deprecated [Array.create_matrix] is an alias for {!Array.make_matrix}. *)
|
||||
val create_matrix: int -> int -> 'a -> 'a array array
|
||||
|
||||
val append : 'a array -> 'a array -> 'a array
|
||||
(** [Array.append v1 v2] returns a fresh array containing the
|
||||
concatenation of the arrays [v1] and [v2]. *)
|
||||
val append: 'a array -> 'a array -> 'a array
|
||||
|
||||
val concat : 'a array list -> 'a array
|
||||
(** Same as [Array.append], but catenates a list of arrays. *)
|
||||
val concat: 'a array list -> 'a array
|
||||
|
||||
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].
|
||||
|
@ -86,19 +87,19 @@ val concat: 'a array list -> 'a array
|
|||
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 sub: 'a array -> int -> int -> 'a array
|
||||
|
||||
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 copy: 'a array -> 'a array
|
||||
|
||||
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 fill: 'a array -> int -> int -> 'a -> unit
|
||||
|
||||
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
|
||||
|
@ -108,49 +109,49 @@ val fill: 'a array -> int -> int -> 'a -> unit
|
|||
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 blit: 'a array -> int -> 'a array -> int -> int -> unit
|
||||
|
||||
val to_list : 'a array -> 'a list
|
||||
(** [Array.to_list a] returns the list of all the elements of [a]. *)
|
||||
val to_list: 'a array -> 'a list
|
||||
|
||||
val of_list : 'a list -> 'a array
|
||||
(** [Array.of_list l] returns a fresh array containing the elements
|
||||
of [l]. *)
|
||||
val of_list: 'a list -> 'a array
|
||||
|
||||
val iter : ('a -> unit) -> 'a array -> unit
|
||||
(** [Array.iter f a] applies function [f] in turn to all
|
||||
the elements of [a]. It is equivalent to
|
||||
[f a.(0); f a.(1); ...; f a.(Array.length a - 1); ()]. *)
|
||||
val iter: ('a -> unit) -> 'a array -> unit
|
||||
|
||||
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 map: ('a -> 'b) -> 'a array -> 'b array
|
||||
|
||||
val iteri : (int -> 'a -> unit) -> 'a array -> unit
|
||||
(** Same as {!Array.iter}, but the
|
||||
function is applied to the index of the element as first argument,
|
||||
and the element itself as second argument. *)
|
||||
val iteri: (int -> 'a -> unit) -> 'a array -> unit
|
||||
|
||||
val mapi : (int -> 'a -> 'b) -> 'a array -> 'b array
|
||||
(** Same as {!Array.map}, but the
|
||||
function is applied to the index of the element as first argument,
|
||||
and the element itself as second argument. *)
|
||||
val mapi: (int -> 'a -> 'b) -> 'a array -> 'b array
|
||||
|
||||
val fold_left : ('a -> 'b -> 'a) -> 'a -> 'b array -> 'a
|
||||
(** [Array.fold_left f x a] computes
|
||||
[f (... (f (f x a.(0)) a.(1)) ...) a.(n-1)],
|
||||
where [n] is the length of the array [a]. *)
|
||||
val fold_left: ('a -> 'b -> 'a) -> 'a -> 'b array -> 'a
|
||||
|
||||
val fold_right : ('b -> 'a -> 'a) -> 'b array -> 'a -> 'a
|
||||
(** [Array.fold_right f a x] computes
|
||||
[f a.(0) (f a.(1) ( ... (f a.(n-1) x) ...))],
|
||||
where [n] is the length of the array [a]. *)
|
||||
val fold_right: ('b -> 'a -> 'a) -> 'b array -> 'a -> 'a
|
||||
|
||||
|
||||
(** {2 Sorting} *)
|
||||
|
||||
|
||||
val sort : ('a -> 'a -> int) -> 'a array -> unit
|
||||
(** Sort an array in increasing order according to a comparison
|
||||
function. The comparison function must return 0 if its arguments
|
||||
compare as equal, a positive integer if the first is greater,
|
||||
|
@ -161,22 +162,20 @@ val fold_right: ('b -> 'a -> 'a) -> 'b array -> 'a -> 'a
|
|||
[Array.sort] is guaranteed to run in constant heap space
|
||||
and logarithmic stack space.
|
||||
|
||||
|
||||
The current implementation uses Heap Sort. It runs in constant
|
||||
stack space.
|
||||
*)
|
||||
val sort : ('a -> 'a -> int) -> 'a array -> unit;;
|
||||
|
||||
val stable_sort : ('a -> 'a -> int) -> 'a array -> unit
|
||||
(** Same as {!Array.sort}, but the sorting algorithm is stable and
|
||||
not guaranteed to use a fixed amount of heap memory.
|
||||
The current implementation is Merge Sort. It uses [n/2]
|
||||
words of heap space, where [n] is the length of the array.
|
||||
It is faster than the current implementation of {!Array.sort}.
|
||||
*)
|
||||
val stable_sort : ('a -> 'a -> int) -> 'a array -> unit;;
|
||||
|
||||
(**/**)
|
||||
(** {2 Undocumented functions} *)
|
||||
|
||||
external unsafe_get: 'a array -> int -> 'a = "%array_unsafe_get"
|
||||
external unsafe_set: 'a array -> int -> 'a -> unit = "%array_unsafe_set"
|
||||
external unsafe_get : 'a array -> int -> 'a = "%array_unsafe_get"
|
||||
external unsafe_set : 'a array -> int -> 'a -> unit = "%array_unsafe_set"
|
||||
|
|
|
@ -14,25 +14,26 @@
|
|||
|
||||
(** Array operations. *)
|
||||
|
||||
(** Return the length (number of elements) of the given array. *)
|
||||
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 [Array.get a n]. *)
|
||||
external get: 'a array -> int -> 'a = "%array_safe_get"
|
||||
|
||||
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 [Array.set a n x]. *)
|
||||
external set: 'a array -> int -> 'a -> unit = "%array_safe_set"
|
||||
|
||||
external make : int -> 'a -> 'a array = "make_vect"
|
||||
(** [Array.make n x] returns a fresh array of length [n],
|
||||
initialized with [x].
|
||||
All the elements of this new array are initially
|
||||
|
@ -44,17 +45,17 @@ external set: 'a array -> int -> 'a -> unit = "%array_safe_set"
|
|||
Raise [Invalid_argument] if [n < 0] or [n > Sys.max_array_length].
|
||||
If the value of [x] is a floating-point number, then the maximum
|
||||
size is only [Sys.max_array_length / 2].*)
|
||||
external make: int -> 'a -> 'a array = "make_vect"
|
||||
|
||||
external create : int -> 'a -> 'a array = "make_vect"
|
||||
(** @deprecated [Array.create] is an alias for {!ArrayLabels.make}. *)
|
||||
external create: int -> 'a -> 'a array = "make_vect"
|
||||
|
||||
val init : int -> f:(int -> 'a) -> 'a array
|
||||
(** [Array.init n f] returns a fresh array of length [n],
|
||||
with element number [i] initialized to the result of [f i].
|
||||
In other terms, [Array.init n f] tabulates the results of [f]
|
||||
applied to the integers [0] to [n-1]. *)
|
||||
val init: int -> f:(int -> 'a) -> 'a array
|
||||
|
||||
val make_matrix : dimx:int -> dimy:int -> 'a -> 'a array array
|
||||
(** [Array.make_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
|
||||
|
@ -66,18 +67,18 @@ val init: int -> f:(int -> 'a) -> 'a array
|
|||
greater than [Sys.max_array_length].
|
||||
If the value of [e] is a floating-point number, then the maximum
|
||||
size is only [Sys.max_array_length / 2]. *)
|
||||
val make_matrix: dimx:int -> dimy:int -> 'a -> 'a array array
|
||||
|
||||
val create_matrix : dimx:int -> dimy:int -> 'a -> 'a array array
|
||||
(** @deprecated [Array.create_matrix] is an alias for {!ArrayLabels.make_matrix}. *)
|
||||
val create_matrix: dimx:int -> dimy:int -> 'a -> 'a array array
|
||||
|
||||
val append : 'a array -> 'a array -> 'a array
|
||||
(** [Array.append v1 v2] returns a fresh array containing the
|
||||
concatenation of the arrays [v1] and [v2]. *)
|
||||
val append: 'a array -> 'a array -> 'a array
|
||||
|
||||
val concat : 'a array list -> 'a array
|
||||
(** Same as [Array.append], but catenates a list of arrays. *)
|
||||
val concat: 'a array list -> 'a array
|
||||
|
||||
val sub : 'a array -> pos:int -> len: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].
|
||||
|
@ -85,19 +86,21 @@ val concat: 'a array list -> 'a array
|
|||
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 sub: 'a array -> pos:int -> len:int -> 'a array
|
||||
|
||||
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 copy: 'a array -> 'a array
|
||||
|
||||
val fill : 'a array -> pos:int -> len: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 fill: 'a array -> pos:int -> len:int -> 'a -> unit
|
||||
|
||||
val blit :
|
||||
src:'a array -> src_pos:int -> dst:'a array -> dst_pos:int -> len: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
|
||||
|
@ -107,51 +110,50 @@ val fill: 'a array -> pos:int -> len:int -> 'a -> unit
|
|||
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 blit: src:'a array -> src_pos:int ->
|
||||
dst:'a array -> dst_pos:int -> len:int -> unit
|
||||
|
||||
val to_list : 'a array -> 'a list
|
||||
(** [Array.to_list a] returns the list of all the elements of [a]. *)
|
||||
val to_list: 'a array -> 'a list
|
||||
|
||||
val of_list : 'a list -> 'a array
|
||||
(** [Array.of_list l] returns a fresh array containing the elements
|
||||
of [l]. *)
|
||||
val of_list: 'a list -> 'a array
|
||||
|
||||
val iter : f:('a -> unit) -> 'a array -> unit
|
||||
(** [Array.iter f a] applies function [f] in turn to all
|
||||
the elements of [a]. It is equivalent to
|
||||
[f a.(0); f a.(1); ...; f a.(Array.length a - 1); ()]. *)
|
||||
val iter: f:('a -> unit) -> 'a array -> unit
|
||||
|
||||
val map : f:('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 map: f:('a -> 'b) -> 'a array -> 'b array
|
||||
|
||||
val iteri : f:(int -> 'a -> unit) -> 'a array -> unit
|
||||
(** Same as {!ArrayLabels.iter}, but the
|
||||
function is applied to the index of the element as first argument,
|
||||
and the element itself as second argument. *)
|
||||
val iteri: f:(int -> 'a -> unit) -> 'a array -> unit
|
||||
|
||||
val mapi : f:(int -> 'a -> 'b) -> 'a array -> 'b array
|
||||
(** Same as {!ArrayLabels.map}, but the
|
||||
function is applied to the index of the element as first argument,
|
||||
and the element itself as second argument. *)
|
||||
val mapi: f:(int -> 'a -> 'b) -> 'a array -> 'b array
|
||||
|
||||
val fold_left : f:('a -> 'b -> 'a) -> init:'a -> 'b array -> 'a
|
||||
(** [Array.fold_left f x a] computes
|
||||
[f (... (f (f x a.(0)) a.(1)) ...) a.(n-1)],
|
||||
where [n] is the length of the array [a]. *)
|
||||
val fold_left: f:('a -> 'b -> 'a) -> init:'a -> 'b array -> 'a
|
||||
|
||||
val fold_right : f:('b -> 'a -> 'a) -> 'b array -> init:'a -> 'a
|
||||
(** [Array.fold_right f a x] computes
|
||||
[f a.(0) (f a.(1) ( ... (f a.(n-1) x) ...))],
|
||||
where [n] is the length of the array [a]. *)
|
||||
val fold_right: f:('b -> 'a -> 'a) -> 'b array -> init:'a -> 'a
|
||||
|
||||
|
||||
|
||||
(** {2 Sorting} *)
|
||||
|
||||
|
||||
val sort : cmp:('a -> 'a -> int) -> 'a array -> unit
|
||||
(** Sort an array in increasing order according to a comparison
|
||||
function. The comparison function must return 0 if its arguments
|
||||
compare as equal, a positive integer if the first is greater,
|
||||
|
@ -166,19 +168,18 @@ val fold_right: f:('b -> 'a -> 'a) -> 'b array -> init:'a -> 'a
|
|||
The current implementation uses Heap Sort. It runs in constant
|
||||
stack space.
|
||||
*)
|
||||
val sort : cmp:('a -> 'a -> int) -> 'a array -> unit;;
|
||||
|
||||
val stable_sort : cmp:('a -> 'a -> int) -> 'a array -> unit
|
||||
(** Same as {!ArrayLabels.sort}, but the sorting algorithm is stable and
|
||||
not guaranteed to use a fixed amount of heap memory.
|
||||
The current implementation is Merge Sort. It uses [n/2]
|
||||
words of heap space, where [n] is the length of the array.
|
||||
It is faster than the current implementation of {!ArrayLabels.sort}.
|
||||
*)
|
||||
val stable_sort : cmp:('a -> 'a -> int) -> 'a array -> unit;;
|
||||
|
||||
(**/**)
|
||||
|
||||
(** {2 Undocumented functions} *)
|
||||
|
||||
external unsafe_get: 'a array -> int -> 'a = "%array_unsafe_get"
|
||||
external unsafe_set: 'a array -> int -> 'a -> unit = "%array_unsafe_set"
|
||||
external unsafe_get : 'a array -> int -> 'a = "%array_unsafe_get"
|
||||
external unsafe_set : 'a array -> int -> 'a -> unit = "%array_unsafe_set"
|
||||
|
|
|
@ -18,9 +18,10 @@
|
|||
concatenated pairwise).
|
||||
*)
|
||||
|
||||
(** The abstract type of buffers. *)
|
||||
type t
|
||||
(** The abstract type of buffers. *)
|
||||
|
||||
val create : int -> t
|
||||
(** [create n] returns a fresh buffer, initially empty.
|
||||
The [n] parameter is the initial size of the internal string
|
||||
that holds the buffer contents. That string is automatically
|
||||
|
@ -33,46 +34,45 @@ type t
|
|||
limit, however. In doubt, take [n = 16] for instance.
|
||||
If [n] is not between 1 and {!Sys.max_string_length}, it will
|
||||
be clipped to that interval. *)
|
||||
val create : int -> t
|
||||
|
||||
val contents : t -> string
|
||||
(** Return a copy of the current contents of the buffer.
|
||||
The buffer itself is unchanged. *)
|
||||
val contents : t -> string
|
||||
|
||||
(** Return the number of characters currently contained in the buffer. *)
|
||||
val length : t -> int
|
||||
(** Return the number of characters currently contained in the buffer. *)
|
||||
|
||||
(** Empty the buffer. *)
|
||||
val clear : t -> unit
|
||||
(** Empty the buffer. *)
|
||||
|
||||
val reset : t -> unit
|
||||
(** Empty the buffer and deallocate the internal string holding the
|
||||
buffer contents, replacing it with the initial internal string
|
||||
of length [n] that was allocated by {!Buffer.create} [n].
|
||||
For long-lived buffers that may have grown a lot, [reset] allows
|
||||
faster reclaimation of the space used by the buffer. *)
|
||||
val reset : t -> unit
|
||||
|
||||
(** [add_char b c] appends the character [c] at the end of the buffer [b]. *)
|
||||
val add_char : t -> char -> unit
|
||||
(** [add_char b c] appends the character [c] at the end of the buffer [b]. *)
|
||||
|
||||
(** [add_string b s] appends the string [s] at the end of the buffer [b]. *)
|
||||
val add_string : t -> string -> unit
|
||||
(** [add_string b s] appends the string [s] at the end of the buffer [b]. *)
|
||||
|
||||
val add_substring : t -> string -> int -> int -> unit
|
||||
(** [add_substring b s ofs len] takes [len] characters from offset
|
||||
[ofs] in string [s] and appends them at the end of the buffer [b]. *)
|
||||
val add_substring : t -> string -> int -> int -> unit
|
||||
|
||||
val add_buffer : t -> t -> unit
|
||||
(** [add_buffer b1 b2] appends the current contents of buffer [b2]
|
||||
at the end of buffer [b1]. [b2] is not modified. *)
|
||||
val add_buffer : t -> t -> unit
|
||||
|
||||
val add_channel : t -> in_channel -> int -> unit
|
||||
(** [add_channel b ic n] reads exactly [n] character from the
|
||||
input channel [ic] and stores them at the end of buffer [b].
|
||||
Raise [End_of_file] if the channel contains fewer than [n]
|
||||
characters. *)
|
||||
val add_channel : t -> in_channel -> int -> unit
|
||||
|
||||
val output_buffer : out_channel -> t -> unit
|
||||
(** [output_buffer oc b] writes the current contents of buffer [b]
|
||||
on the output channel [oc]. *)
|
||||
val output_buffer : out_channel -> t -> unit
|
||||
|
||||
|
|
|
@ -19,15 +19,15 @@
|
|||
Caml functions, or raise registered Caml exceptions.
|
||||
*)
|
||||
|
||||
val register : string -> 'a -> unit
|
||||
(** [Callback.register n v] registers the value [v] under
|
||||
the name [n]. C code can later retrieve a handle to [v]
|
||||
by calling [caml_named_value(n)]. *)
|
||||
val register: string -> 'a -> unit
|
||||
|
||||
val register_exception : string -> exn -> unit
|
||||
(** [Callback.register_exception n exn] registers the
|
||||
exception contained in the exception value [exn]
|
||||
under the name [n]. C code can later retrieve a handle to
|
||||
the exception by calling [caml_named_value(n)]. The exception
|
||||
value thus obtained is suitable for passign as first argument
|
||||
to [raise_constant] or [raise_with_arg]. *)
|
||||
val register_exception: string -> exn -> unit
|
||||
|
|
|
@ -14,25 +14,25 @@
|
|||
|
||||
(** Character operations. *)
|
||||
|
||||
(** Return the ASCII code of the argument. *)
|
||||
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.chr"] if the argument is
|
||||
outside the range 0--255. *)
|
||||
val chr: int -> char
|
||||
|
||||
val escaped : char -> string
|
||||
(** Return a string representing the given character,
|
||||
with special characters escaped following the lexical conventions
|
||||
of Objective Caml. *)
|
||||
val escaped : char -> string
|
||||
|
||||
val lowercase : char -> char
|
||||
(** Convert the given character to its equivalent lowercase character. *)
|
||||
val lowercase: char -> char
|
||||
|
||||
val uppercase : char -> char
|
||||
(** Convert the given character to its equivalent uppercase character. *)
|
||||
val uppercase: char -> char
|
||||
|
||||
(**/**)
|
||||
|
||||
external unsafe_chr: int -> char = "%identity"
|
||||
external unsafe_chr : int -> char = "%identity"
|
||||
|
|
|
@ -20,27 +20,27 @@
|
|||
that digest. The algorithm used is MD5.
|
||||
*)
|
||||
|
||||
(** The type of digests: 16-character strings. *)
|
||||
type t = string
|
||||
(** The type of digests: 16-character strings. *)
|
||||
|
||||
val string : string -> t
|
||||
(** Return the digest of the given string. *)
|
||||
val string: string -> t
|
||||
|
||||
val substring : string -> int -> int -> t
|
||||
(** [Digest.substring s ofs len] returns the digest of the substring
|
||||
of [s] starting at character number [ofs] and containing [len]
|
||||
characters. *)
|
||||
val substring: string -> int -> int -> t
|
||||
|
||||
external channel : in_channel -> int -> t = "md5_chan"
|
||||
(** [Digest.channel ic len] reads [len] characters from channel [ic]
|
||||
and returns their digest. *)
|
||||
external channel: in_channel -> int -> t = "md5_chan"
|
||||
|
||||
val file : string -> t
|
||||
(** Return the digest of the file whose name is given. *)
|
||||
val file: string -> t
|
||||
|
||||
val output : out_channel -> t -> unit
|
||||
(** Write a digest on the given output channel. *)
|
||||
val output: out_channel -> t -> unit
|
||||
|
||||
val input : in_channel -> t
|
||||
(** Read a digest from the given input channel. *)
|
||||
val input: in_channel -> t
|
||||
|
||||
|
|
|
@ -14,55 +14,56 @@
|
|||
|
||||
(** Operations on file names. *)
|
||||
|
||||
(** The conventional name for the current directory (e.g. [.] in Unix). *)
|
||||
val current_dir_name : string
|
||||
(** The conventional name for the current directory (e.g. [.] in Unix). *)
|
||||
|
||||
val parent_dir_name : string
|
||||
(** The conventional name for the parent of the current directory
|
||||
(e.g. [..] in Unix). *)
|
||||
val parent_dir_name : string
|
||||
|
||||
val concat : string -> string -> string
|
||||
(** [concat dir file] returns a file name that designates file
|
||||
[file] in directory [dir]. *)
|
||||
val concat : string -> string -> string
|
||||
|
||||
val is_relative : string -> bool
|
||||
(** Return [true] if the file name is relative to the current
|
||||
directory, [false] if it is absolute (i.e. in Unix, starts
|
||||
with [/]). *)
|
||||
val is_relative : string -> bool
|
||||
|
||||
val is_implicit : string -> bool
|
||||
(** Return [true] if the file name is relative and does not start
|
||||
with an explicit reference to the current directory ([./] or
|
||||
[../] in Unix), [false] if it starts with an explicit reference
|
||||
to the root directory or the current directory. *)
|
||||
val is_implicit : string -> bool
|
||||
|
||||
val check_suffix : string -> string -> bool
|
||||
(** [check_suffix name suff] returns [true] if the filename [name]
|
||||
ends with the suffix [suff]. *)
|
||||
val check_suffix : string -> string -> bool
|
||||
|
||||
val chop_suffix : string -> string -> string
|
||||
(** [chop_suffix name suff] removes the suffix [suff] from
|
||||
the filename [name]. The behavior is undefined if [name] does not
|
||||
end with the suffix [suff]. *)
|
||||
val chop_suffix : string -> string -> string
|
||||
|
||||
val chop_extension : string -> string
|
||||
(** Return the given file name without its extension. The extension
|
||||
is the shortest suffix starting with a period, [.xyz] for instance.
|
||||
|
||||
Raise [Invalid_argument] if the given name does not contain
|
||||
a period. *)
|
||||
val chop_extension : string -> string
|
||||
|
||||
val basename : string -> string
|
||||
(** Split a file name into directory name / base file name.
|
||||
{!Filename.concat} [(]{!Filename.dirname}[ name) (]{!Filename.basename}[ name)]
|
||||
returns a file name which is equivalent to [name]. Moreover, after setting the
|
||||
current directory to {!Filename.dirname}[ name] (with {!Sys.chdir}),
|
||||
references to {!Filename.basename}[ name] (which is a relative file name)
|
||||
designate the same file as [name] before the call to {!Sys.chdir}. *)
|
||||
val basename : string -> string
|
||||
|
||||
(** See {!Filename.dirname}. *)
|
||||
val dirname : string -> string
|
||||
(** See {!Filename.dirname}. *)
|
||||
|
||||
val temp_file : string -> string -> string
|
||||
(** [temp_file prefix suffix] returns the name of a
|
||||
fresh temporary file in the temporary directory.
|
||||
The base name of the temporary file is formed by concatenating
|
||||
|
@ -78,10 +79,9 @@ val dirname : string -> string
|
|||
Under MacOS, the name of the temporary directory is given
|
||||
by the environment variable [TempFolder]; if not set,
|
||||
temporary files are created in the current directory. *)
|
||||
val temp_file : string -> string -> string
|
||||
|
||||
val quote : string -> string
|
||||
(** Return a quoted version of a file name, suitable for use as
|
||||
one argument in a shell command line, escaping any shell
|
||||
meta-characters. *)
|
||||
val quote : string -> string;;
|
||||
|
||||
|
|
|
@ -70,7 +70,7 @@
|
|||
|
||||
(** {2 Boxes} *)
|
||||
|
||||
val open_box : int -> unit;;
|
||||
val open_box : int -> unit
|
||||
(** [open_box d] opens a new pretty-printing box
|
||||
with offset [d].
|
||||
This box is the general purpose pretty-printing box.
|
||||
|
@ -82,42 +82,42 @@ val open_box : int -> unit;;
|
|||
When a new line is printed in the box, [d] is added to the
|
||||
current indentation. *)
|
||||
|
||||
val close_box : unit -> unit;;
|
||||
val close_box : unit -> unit
|
||||
(** Close the most recently opened pretty-printing box. *)
|
||||
|
||||
(** {2 Formatting functions} *)
|
||||
|
||||
val print_string : string -> unit;;
|
||||
val print_string : string -> unit
|
||||
(** [print_string str] prints [str] in the current box. *)
|
||||
|
||||
val print_as : int -> string -> unit;;
|
||||
val print_as : int -> string -> unit
|
||||
(** [print_as len str] prints [str] in the
|
||||
current box. The pretty-printer formats [str] as if
|
||||
it were of length [len]. *)
|
||||
|
||||
val print_int : int -> unit;;
|
||||
val print_int : int -> unit
|
||||
(** Print an integer in the current box. *)
|
||||
|
||||
val print_float : float -> unit;;
|
||||
val print_float : float -> unit
|
||||
(** Print a floating point number in the current box. *)
|
||||
|
||||
val print_char : char -> unit;;
|
||||
val print_char : char -> unit
|
||||
(** Print a character in the current box. *)
|
||||
|
||||
val print_bool : bool -> unit;;
|
||||
val print_bool : bool -> unit
|
||||
(** Print a boolean in the current box. *)
|
||||
|
||||
|
||||
(** {2 Break hints} *)
|
||||
|
||||
val print_space : unit -> unit;;
|
||||
val print_space : unit -> unit
|
||||
(** [print_space ()] is used to separate items (typically to print
|
||||
a space between two words).
|
||||
It indicates that the line may be split at this
|
||||
point. It either prints one space or splits the line.
|
||||
It is equivalent to [print_break 1 0]. *)
|
||||
|
||||
val print_cut : unit -> unit;;
|
||||
val print_cut : unit -> unit
|
||||
(** [print_cut ()] is used to mark a good break position.
|
||||
It indicates that the line may be split at this
|
||||
point. It either prints nothing or splits the line.
|
||||
|
@ -125,7 +125,7 @@ val print_cut : unit -> unit;;
|
|||
point, without printing spaces or adding indentation.
|
||||
It is equivalent to [print_break 0 0]. *)
|
||||
|
||||
val print_break : int -> int -> unit;;
|
||||
val print_break : int -> int -> unit
|
||||
(** Insert a break hint in a pretty-printing box.
|
||||
[print_break nspaces offset] indicates that the line may
|
||||
be split (a newline character is printed) at this point,
|
||||
|
@ -135,18 +135,18 @@ val print_break : int -> int -> unit;;
|
|||
the current indentation. If the line is not split,
|
||||
[nspaces] spaces are printed. *)
|
||||
|
||||
val print_flush : unit -> unit;;
|
||||
val print_flush : unit -> unit
|
||||
(** Flush the pretty printer: all opened boxes are closed,
|
||||
and all pending text is displayed. *)
|
||||
|
||||
val print_newline : unit -> unit;;
|
||||
val print_newline : unit -> unit
|
||||
(** Equivalent to [print_flush] followed by a new line. *)
|
||||
|
||||
val force_newline : unit -> unit;;
|
||||
val force_newline : unit -> unit
|
||||
(** Force a newline in the current box. Not the normal way of
|
||||
pretty-printing, you should prefer break hints. *)
|
||||
|
||||
val print_if_newline : unit -> unit;;
|
||||
val print_if_newline : unit -> unit
|
||||
(** Execute the next formatting command if the preceding line
|
||||
has just been split. Otherwise, ignore the next formatting
|
||||
command. *)
|
||||
|
@ -154,20 +154,20 @@ val print_if_newline : unit -> unit;;
|
|||
|
||||
(** {2 Margin} *)
|
||||
|
||||
val set_margin : int -> unit;;
|
||||
val set_margin : int -> unit
|
||||
(** [set_margin d] sets the value of the right margin
|
||||
to [d] (in characters): this value is used to detect line
|
||||
overflows that leads to split lines.
|
||||
Nothing happens if [d] is smaller than 2 or
|
||||
bigger than 999999999. *)
|
||||
|
||||
val get_margin : unit -> int;;
|
||||
val get_margin : unit -> int
|
||||
(** Return the position of the right margin. *)
|
||||
|
||||
|
||||
(** {2 Maximum indentation limit} *)
|
||||
|
||||
val set_max_indent : int -> unit;;
|
||||
val set_max_indent : int -> unit
|
||||
(** [set_max_indent d] sets the value of the maximum
|
||||
indentation limit to [d] (in characters):
|
||||
once this limit is reached, boxes are rejected to the left,
|
||||
|
@ -175,13 +175,13 @@ val set_max_indent : int -> unit;;
|
|||
Nothing happens if [d] is smaller than 2 or
|
||||
bigger than 999999999. *)
|
||||
|
||||
val get_max_indent : unit -> int;;
|
||||
val get_max_indent : unit -> int
|
||||
(** Return the value of the maximum indentation limit (in characters). *)
|
||||
|
||||
|
||||
(** {2 Formatting depth: maximum number of boxes allowed before ellipsis} *)
|
||||
|
||||
val set_max_boxes : int -> unit;;
|
||||
val set_max_boxes : int -> unit
|
||||
(** [set_max_boxes max] sets the maximum number
|
||||
of boxes simultaneously opened.
|
||||
Material inside boxes nested deeper is printed as an
|
||||
|
@ -189,21 +189,21 @@ val set_max_boxes : int -> unit;;
|
|||
[get_ellipsis_text ()]).
|
||||
Nothing happens if [max] is not greater than 1. *)
|
||||
|
||||
val get_max_boxes : unit -> int;;
|
||||
val get_max_boxes : unit -> int
|
||||
(** Return the maximum number of boxes allowed before ellipsis. *)
|
||||
|
||||
val over_max_boxes : unit -> bool;;
|
||||
val over_max_boxes : unit -> bool
|
||||
(** Test if the maximum number of boxes allowed have already been opened. *)
|
||||
|
||||
|
||||
(** {2 Advanced formatting} *)
|
||||
|
||||
val open_hbox : unit -> unit;;
|
||||
val open_hbox : unit -> unit
|
||||
(** [open_hbox ()] opens a new pretty-printing box.
|
||||
This box is ``horizontal'': the line is not split in this box
|
||||
(new lines may still occur inside boxes nested deeper). *)
|
||||
|
||||
val open_vbox : int -> unit;;
|
||||
val open_vbox : int -> unit
|
||||
(** [open_vbox d] opens a new pretty-printing box
|
||||
with offset [d].
|
||||
This box is ``vertical'': every break hint inside this
|
||||
|
@ -211,7 +211,7 @@ val open_vbox : int -> unit;;
|
|||
When a new line is printed in the box, [d] is added to the
|
||||
current indentation. *)
|
||||
|
||||
val open_hvbox : int -> unit;;
|
||||
val open_hvbox : int -> unit
|
||||
(** [open_hvbox d] opens a new pretty-printing box
|
||||
with offset [d].
|
||||
This box is ``horizontal-vertical'': it behaves as an
|
||||
|
@ -220,7 +220,7 @@ val open_hvbox : int -> unit;;
|
|||
When a new line is printed in the box, [d] is added to the
|
||||
current indentation. *)
|
||||
|
||||
val open_hovbox : int -> unit;;
|
||||
val open_hovbox : int -> unit
|
||||
(** [open_hovbox d] opens a new pretty-printing box
|
||||
with offset [d].
|
||||
This box is ``horizontal or vertical'': break hints
|
||||
|
@ -232,13 +232,13 @@ val open_hovbox : int -> unit;;
|
|||
|
||||
(** {2 Tabulations} *)
|
||||
|
||||
val open_tbox : unit -> unit;;
|
||||
val open_tbox : unit -> unit
|
||||
(** Open a tabulation box. *)
|
||||
|
||||
val close_tbox : unit -> unit;;
|
||||
val close_tbox : unit -> unit
|
||||
(** Close the most recently opened tabulation box. *)
|
||||
|
||||
val print_tbreak : int -> int -> unit;;
|
||||
val print_tbreak : int -> int -> unit
|
||||
(** Break hint in a tabulation box.
|
||||
[print_tbreak spaces offset] moves the insertion point to
|
||||
the next tabulation ([spaces] being added to this position).
|
||||
|
@ -250,33 +250,33 @@ val print_tbreak : int -> int -> unit;;
|
|||
If a new line is printed, [offset] is added to the current
|
||||
indentation. *)
|
||||
|
||||
val set_tab : unit -> unit;;
|
||||
val set_tab : unit -> unit
|
||||
(** Set a tabulation mark at the current insertion point. *)
|
||||
|
||||
val print_tab : unit -> unit;;
|
||||
val print_tab : unit -> unit
|
||||
(** [print_tab ()] is equivalent to [print_tbreak (0,0)]. *)
|
||||
|
||||
|
||||
(** {2 Ellipsis} *)
|
||||
|
||||
val set_ellipsis_text : string -> unit;;
|
||||
val set_ellipsis_text : string -> unit
|
||||
(** Set the text of the ellipsis printed when too many boxes
|
||||
are opened (a single dot, [.], by default). *)
|
||||
|
||||
val get_ellipsis_text : unit -> string;;
|
||||
val get_ellipsis_text : unit -> string
|
||||
(** Return the text of the ellipsis. *)
|
||||
|
||||
|
||||
(** {2 Redirecting formatter output} *)
|
||||
|
||||
val set_formatter_out_channel : out_channel -> unit;;
|
||||
val set_formatter_out_channel : out_channel -> unit
|
||||
(** Redirect the pretty-printer output to the given channel. *)
|
||||
|
||||
|
||||
(** {2 Changing the meaning of printing material} *)
|
||||
|
||||
val set_formatter_output_functions :
|
||||
(string -> int -> int -> unit) -> (unit -> unit) -> unit;;
|
||||
(string -> int -> int -> unit) -> (unit -> unit) -> unit
|
||||
(** [set_formatter_output_functions out flush] redirects the
|
||||
pretty-printer output to the functions [out] and [flush].
|
||||
The [out] function performs the pretty-printer output.
|
||||
|
@ -287,15 +287,15 @@ val set_formatter_output_functions :
|
|||
[print_flush] or [print_newline]. *)
|
||||
|
||||
val get_formatter_output_functions :
|
||||
unit -> (string -> int -> int -> unit) * (unit -> unit);;
|
||||
unit -> (string -> int -> int -> unit) * (unit -> unit)
|
||||
(** Return the current output functions of the pretty-printer. *)
|
||||
|
||||
|
||||
(** {2 Changing the meaning of pretty printing (indentation, line breaking, and printing material)} *)
|
||||
|
||||
val set_all_formatter_output_functions :
|
||||
out:(string -> int -> int -> unit) -> flush:(unit -> unit) ->
|
||||
newline:(unit -> unit) -> spaces:(int -> unit) -> unit;;
|
||||
out:(string -> int -> int -> unit) -> flush:(unit -> unit) ->
|
||||
newline:(unit -> unit) -> spaces:(int -> unit) -> unit
|
||||
(** [set_all_formatter_output_functions out flush outnewline outspace]
|
||||
redirects the pretty-printer output to the functions
|
||||
[out] and [flush] as described in
|
||||
|
@ -312,16 +312,17 @@ val set_all_formatter_output_functions :
|
|||
[outspace] and [outnewline] are [out (String.make n ' ') 0 n]
|
||||
and [out "\n" 0 1]. *)
|
||||
|
||||
val get_all_formatter_output_functions : unit ->
|
||||
(string -> int -> int -> unit) * (unit -> unit) *
|
||||
(unit -> unit) * (int -> unit);;
|
||||
val get_all_formatter_output_functions :
|
||||
unit ->
|
||||
(string -> int -> int -> unit) * (unit -> unit) * (unit -> unit) *
|
||||
(int -> unit)
|
||||
(** Return the current output functions of the pretty-printer,
|
||||
including line breaking and indentation functions. *)
|
||||
|
||||
|
||||
(** {2 Multiple formatted output} *)
|
||||
|
||||
type formatter;;
|
||||
type formatter
|
||||
(** Abstract data type corresponding to a pretty-printer and
|
||||
all its machinery.
|
||||
Defining new pretty-printers permits the output of
|
||||
|
@ -336,40 +337,40 @@ type formatter;;
|
|||
formatter with explicit output and flushing functions
|
||||
(convenient to output material to strings for instance). *)
|
||||
|
||||
val formatter_of_out_channel : out_channel -> formatter;;
|
||||
val formatter_of_out_channel : out_channel -> formatter
|
||||
(** [formatter_of_out_channel oc] returns a new formatter that
|
||||
writes to the corresponding channel [oc]. *)
|
||||
|
||||
val std_formatter : formatter;;
|
||||
val std_formatter : formatter
|
||||
(** The standard formatter used by the formatting functions
|
||||
above. It is defined as [formatter_of_out_channel stdout]. *)
|
||||
|
||||
val err_formatter : formatter;;
|
||||
val err_formatter : formatter
|
||||
(** A formatter to use with formatting functions below for
|
||||
output to standard error. It is defined as
|
||||
[formatter_of_out_channel stderr]. *)
|
||||
|
||||
val formatter_of_buffer : Buffer.t -> formatter;;
|
||||
val formatter_of_buffer : Buffer.t -> formatter
|
||||
(** [formatter_of_buffer b] returns a new formatter writing to
|
||||
buffer [b]. As usual, the formatter has to be flushed at
|
||||
the end of pretty printing, using [pp_print_flush] or
|
||||
[pp_print_newline], to display all the pending material. *)
|
||||
|
||||
val stdbuf : Buffer.t;;
|
||||
val stdbuf : Buffer.t
|
||||
(** The string buffer in which [str_formatter] writes. *)
|
||||
|
||||
val str_formatter : formatter;;
|
||||
val str_formatter : formatter
|
||||
(** A formatter to use with formatting functions below for
|
||||
output to the [stdbuf] string buffer.
|
||||
[str_formatter] is defined as
|
||||
[formatter_of_buffer stdbuf]. *)
|
||||
|
||||
val flush_str_formatter : unit -> string;;
|
||||
val flush_str_formatter : unit -> string
|
||||
(** Returns the material printed with [str_formatter], flushes
|
||||
the formatter and reset the corresponding buffer. *)
|
||||
|
||||
val make_formatter :
|
||||
(string -> int -> int -> unit) -> (unit -> unit) -> formatter;;
|
||||
(string -> int -> int -> unit) -> (unit -> unit) -> formatter
|
||||
(** [make_formatter out flush] returns a new formatter that
|
||||
writes according to the output function [out], and the flushing
|
||||
function [flush]. Hence, a formatter to the out channel [oc]
|
||||
|
@ -378,50 +379,51 @@ val make_formatter :
|
|||
|
||||
(** {2 Basic functions to use with formatters} *)
|
||||
|
||||
val pp_open_hbox : formatter -> unit -> unit;;
|
||||
val pp_open_vbox : formatter -> int -> unit;;
|
||||
val pp_open_hvbox : formatter -> int -> unit;;
|
||||
val pp_open_hovbox : formatter -> int -> unit;;
|
||||
val pp_open_box : formatter -> int -> unit;;
|
||||
val pp_close_box : formatter -> unit -> unit;;
|
||||
val pp_print_string : formatter -> string -> unit;;
|
||||
val pp_print_as : formatter -> int -> string -> unit;;
|
||||
val pp_print_int : formatter -> int -> unit;;
|
||||
val pp_print_float : formatter -> float -> unit;;
|
||||
val pp_print_char : formatter -> char -> unit;;
|
||||
val pp_print_bool : formatter -> bool -> unit;;
|
||||
val pp_print_break : formatter -> int -> int -> unit;;
|
||||
val pp_print_cut : formatter -> unit -> unit;;
|
||||
val pp_print_space : formatter -> unit -> unit;;
|
||||
val pp_force_newline : formatter -> unit -> unit;;
|
||||
val pp_print_flush : formatter -> unit -> unit;;
|
||||
val pp_print_newline : formatter -> unit -> unit;;
|
||||
val pp_print_if_newline : formatter -> unit -> unit;;
|
||||
val pp_open_tbox : formatter -> unit -> unit;;
|
||||
val pp_close_tbox : formatter -> unit -> unit;;
|
||||
val pp_print_tbreak : formatter -> int -> int -> unit;;
|
||||
val pp_set_tab : formatter -> unit -> unit;;
|
||||
val pp_print_tab : formatter -> unit -> unit;;
|
||||
val pp_set_margin : formatter -> int -> unit;;
|
||||
val pp_get_margin : formatter -> unit -> int;;
|
||||
val pp_set_max_indent : formatter -> int -> unit;;
|
||||
val pp_get_max_indent : formatter -> unit -> int;;
|
||||
val pp_set_max_boxes : formatter -> int -> unit;;
|
||||
val pp_get_max_boxes : formatter -> unit -> int;;
|
||||
val pp_over_max_boxes : formatter -> unit -> bool;;
|
||||
val pp_set_ellipsis_text : formatter -> string -> unit;;
|
||||
val pp_get_ellipsis_text : formatter -> unit -> string;;
|
||||
val pp_set_formatter_out_channel : formatter -> out_channel -> unit;;
|
||||
val pp_set_formatter_output_functions : formatter ->
|
||||
(string -> int -> int -> unit) -> (unit -> unit) -> unit;;
|
||||
val pp_get_formatter_output_functions : formatter -> unit ->
|
||||
(string -> int -> int -> unit) * (unit -> unit);;
|
||||
val pp_set_all_formatter_output_functions : formatter ->
|
||||
out:(string -> int -> int -> unit) -> flush:(unit -> unit) ->
|
||||
newline:(unit -> unit) -> spaces:(int -> unit) -> unit;;
|
||||
val pp_get_all_formatter_output_functions : formatter -> unit ->
|
||||
(string -> int -> int -> unit) * (unit -> unit) *
|
||||
(unit -> unit) * (int -> unit);;
|
||||
val pp_open_hbox : formatter -> unit -> unit
|
||||
val pp_open_vbox : formatter -> int -> unit
|
||||
val pp_open_hvbox : formatter -> int -> unit
|
||||
val pp_open_hovbox : formatter -> int -> unit
|
||||
val pp_open_box : formatter -> int -> unit
|
||||
val pp_close_box : formatter -> unit -> unit
|
||||
val pp_print_string : formatter -> string -> unit
|
||||
val pp_print_as : formatter -> int -> string -> unit
|
||||
val pp_print_int : formatter -> int -> unit
|
||||
val pp_print_float : formatter -> float -> unit
|
||||
val pp_print_char : formatter -> char -> unit
|
||||
val pp_print_bool : formatter -> bool -> unit
|
||||
val pp_print_break : formatter -> int -> int -> unit
|
||||
val pp_print_cut : formatter -> unit -> unit
|
||||
val pp_print_space : formatter -> unit -> unit
|
||||
val pp_force_newline : formatter -> unit -> unit
|
||||
val pp_print_flush : formatter -> unit -> unit
|
||||
val pp_print_newline : formatter -> unit -> unit
|
||||
val pp_print_if_newline : formatter -> unit -> unit
|
||||
val pp_open_tbox : formatter -> unit -> unit
|
||||
val pp_close_tbox : formatter -> unit -> unit
|
||||
val pp_print_tbreak : formatter -> int -> int -> unit
|
||||
val pp_set_tab : formatter -> unit -> unit
|
||||
val pp_print_tab : formatter -> unit -> unit
|
||||
val pp_set_margin : formatter -> int -> unit
|
||||
val pp_get_margin : formatter -> unit -> int
|
||||
val pp_set_max_indent : formatter -> int -> unit
|
||||
val pp_get_max_indent : formatter -> unit -> int
|
||||
val pp_set_max_boxes : formatter -> int -> unit
|
||||
val pp_get_max_boxes : formatter -> unit -> int
|
||||
val pp_over_max_boxes : formatter -> unit -> bool
|
||||
val pp_set_ellipsis_text : formatter -> string -> unit
|
||||
val pp_get_ellipsis_text : formatter -> unit -> string
|
||||
val pp_set_formatter_out_channel : formatter -> out_channel -> unit
|
||||
val pp_set_formatter_output_functions :
|
||||
formatter -> (string -> int -> int -> unit) -> (unit -> unit) -> unit
|
||||
val pp_get_formatter_output_functions :
|
||||
formatter -> unit -> (string -> int -> int -> unit) * (unit -> unit)
|
||||
val pp_set_all_formatter_output_functions :
|
||||
formatter -> out:(string -> int -> int -> unit) -> flush:(unit -> unit) ->
|
||||
newline:(unit -> unit) -> spaces:(int -> unit) -> unit
|
||||
val pp_get_all_formatter_output_functions :
|
||||
formatter -> unit ->
|
||||
(string -> int -> int -> unit) * (unit -> unit) * (unit -> unit) *
|
||||
(int -> unit)
|
||||
(** These functions are the basic ones: usual functions
|
||||
operating on the standard formatter are defined via partial
|
||||
evaluation of these primitives. For instance,
|
||||
|
@ -430,7 +432,7 @@ val pp_get_all_formatter_output_functions : formatter -> unit ->
|
|||
|
||||
(** {2 [printf] like functions for pretty-printing.} *)
|
||||
|
||||
val fprintf : formatter -> ('a, formatter, unit) format -> 'a;;
|
||||
val fprintf : formatter -> ('a, formatter, unit) format -> 'a
|
||||
(** [fprintf ff format arg1 ... argN] formats the arguments
|
||||
[arg1] to [argN] according to the format string [format],
|
||||
and outputs the resulting string on the formatter [ff].
|
||||
|
@ -477,13 +479,13 @@ val fprintf : formatter -> ('a, formatter, unit) format -> 'a;;
|
|||
[open_box (); print_string "x ="; print_space (); print_int 1; close_box ()].
|
||||
It prints [x = 1] within a pretty-printing box. *)
|
||||
|
||||
val printf : ('a, formatter, unit) format -> 'a;;
|
||||
val printf : ('a, formatter, unit) format -> 'a
|
||||
(** Same as [fprintf] above, but output on [std_formatter]. *)
|
||||
|
||||
val eprintf: ('a, formatter, unit) format -> 'a;;
|
||||
val eprintf : ('a, formatter, unit) format -> 'a
|
||||
(** Same as [fprintf] above, but output on [err_formatter]. *)
|
||||
|
||||
val sprintf: ('a, unit, string) format -> 'a;;
|
||||
val sprintf : ('a, unit, string) format -> 'a
|
||||
(** Same as [printf] above, but instead of printing on a formatter,
|
||||
return a string containing the result of formatting the arguments.
|
||||
Note that the pretty-printer queue is flushed at the end of each
|
||||
|
@ -495,7 +497,7 @@ val sprintf: ('a, unit, string) format -> 'a;;
|
|||
predefined formatter [str_formatter] and call [flush_str_formatter
|
||||
()] to get the result. *)
|
||||
|
||||
val bprintf: Buffer.t -> ('a, formatter, unit) format -> 'a;;
|
||||
val bprintf : Buffer.t -> ('a, formatter, unit) format -> 'a
|
||||
(** Same as [sprintf] above, but instead of printing on a string,
|
||||
writes into the given extensible buffer.
|
||||
As for [sprintf], the pretty-printer queue is flushed at the end of each
|
||||
|
|
128
stdlib/gc.mli
128
stdlib/gc.mli
|
@ -14,6 +14,47 @@
|
|||
|
||||
(** Memory management control and statistics; finalised values. *)
|
||||
|
||||
type stat =
|
||||
{ minor_words : float;
|
||||
(** Number of words allocated in the minor heap since
|
||||
the program was started. This number is accurate in the
|
||||
byte-code runtime, but only approximate in the native runtime. *)
|
||||
promoted_words : float;
|
||||
(** Number of words allocated in the minor heap that
|
||||
survived a minor collection and were moved to the major heap
|
||||
since the program was started. *)
|
||||
major_words : float;
|
||||
(** Number of words allocated in the major heap, including
|
||||
the promoted words, since the program was started. *)
|
||||
minor_collections : int;
|
||||
(** Number of minor collections since the program was started. *)
|
||||
major_collections : int;
|
||||
(** Number of major collection cycles, not counting
|
||||
the current cycle, since the program was started. *)
|
||||
heap_words : int;
|
||||
(** Total size of the major heap, in words. *)
|
||||
heap_chunks : int;
|
||||
(** Number of times the major heap size was increased
|
||||
since the program was started (including the initial allocation
|
||||
of the heap). *)
|
||||
live_words : int;
|
||||
(** Number of words of live data in the major heap, including the header words.*)
|
||||
live_blocks : int;
|
||||
(** Number of live blocks in the major heap. *)
|
||||
free_words : int;
|
||||
(** Number of words in the free list. *)
|
||||
free_blocks : int;
|
||||
(** Number of blocks in the free list. *)
|
||||
largest_free : int;
|
||||
(** Size (in words) of the largest block in the free list. *)
|
||||
fragments : int;
|
||||
(** Number of wasted words due to fragmentation. These are
|
||||
1-words free blocks placed between two live blocks. They
|
||||
cannot be inserted in the free list, thus they are not available
|
||||
for allocation. *)
|
||||
compactions : int;
|
||||
(** Number of heap compactions since the program was started. *)
|
||||
}
|
||||
(** The memory management counters are returned in a [stat] record.
|
||||
|
||||
The total amount of memory allocated by the program since it was started
|
||||
|
@ -21,59 +62,17 @@
|
|||
the word size (4 on a 32-bit machine, 8 on a 64-bit machine) to get
|
||||
the number of bytes.
|
||||
*)
|
||||
type stat = {
|
||||
minor_words : float;
|
||||
(** Number of words allocated in the minor heap since
|
||||
the program was started. This number is accurate in the
|
||||
byte-code runtime, but only approximate in the native runtime. *)
|
||||
promoted_words : float;
|
||||
(** Number of words allocated in the minor heap that
|
||||
survived a minor collection and were moved to the major heap
|
||||
since the program was started. *)
|
||||
major_words : float;
|
||||
(** Number of words allocated in the major heap, including
|
||||
the promoted words, since the program was started. *)
|
||||
minor_collections : int;
|
||||
(** Number of minor collections since the program was started. *)
|
||||
major_collections : int;
|
||||
(** Number of major collection cycles, not counting
|
||||
the current cycle, since the program was started. *)
|
||||
heap_words : int;
|
||||
(** Total size of the major heap, in words. *)
|
||||
heap_chunks : int;
|
||||
(** Number of times the major heap size was increased
|
||||
since the program was started (including the initial allocation
|
||||
of the heap). *)
|
||||
live_words : int;
|
||||
(** Number of words of live data in the major heap, including the header words.*)
|
||||
live_blocks : int;
|
||||
(** Number of live blocks in the major heap. *)
|
||||
free_words : int;
|
||||
(** Number of words in the free list. *)
|
||||
free_blocks : int;
|
||||
(** Number of blocks in the free list. *)
|
||||
largest_free : int;
|
||||
(** Size (in words) of the largest block in the free list. *)
|
||||
fragments : int;
|
||||
(** Number of wasted words due to fragmentation. These are
|
||||
1-words free blocks placed between two live blocks. They
|
||||
cannot be inserted in the free list, thus they are not available
|
||||
for allocation. *)
|
||||
compactions : int;
|
||||
(** Number of heap compactions since the program was started. *)
|
||||
}
|
||||
|
||||
(** The GC parameters are given as a [control] record. *)
|
||||
type control = {
|
||||
mutable minor_heap_size : int;
|
||||
type control =
|
||||
{ mutable minor_heap_size : int;
|
||||
(** The size (in words) of the minor heap. Changing
|
||||
this parameter will trigger a minor collection. Default: 32k. *)
|
||||
|
||||
mutable major_heap_increment : int;
|
||||
mutable major_heap_increment : int;
|
||||
(** The minimum number of words to add to the
|
||||
major heap when increasing it. Default: 62k. *)
|
||||
|
||||
mutable space_overhead : int;
|
||||
mutable space_overhead : int;
|
||||
(** The major GC speed is computed from this parameter.
|
||||
This is the memory that will be "wasted" because the GC does not
|
||||
immediatly collect unreachable blocks. It is expressed as a
|
||||
|
@ -83,7 +82,7 @@ type control = {
|
|||
The computation of the GC speed assumes that the amount
|
||||
of live data is constant. Default: 42. *)
|
||||
|
||||
mutable verbose : int;
|
||||
mutable verbose : int;
|
||||
(** This value controls the GC messages on standard error output.
|
||||
It is a sum of some of the following flags, to print messages
|
||||
on the corresponding events:
|
||||
|
@ -98,7 +97,7 @@ type control = {
|
|||
- [0x100] Bytecode executable search at start-up.
|
||||
Default: 0. *)
|
||||
|
||||
mutable max_overhead : int;
|
||||
mutable max_overhead : int;
|
||||
(** Heap compaction is triggered when the estimated amount
|
||||
of free memory is more than [max_overhead] percent of the amount
|
||||
of live data. If [max_overhead] is set to 0, heap
|
||||
|
@ -107,52 +106,54 @@ type control = {
|
|||
If [max_overhead >= 1000000], compaction is never triggered.
|
||||
Default: 1000000. *)
|
||||
|
||||
mutable stack_limit : int;
|
||||
mutable stack_limit : int;
|
||||
(** The maximum size of the stack (in words). This is only
|
||||
relevant to the byte-code runtime, as the native code runtime
|
||||
uses the operating system's stack. Default: 256k. *)
|
||||
uses the operating system's stack. Default: 256k. *)
|
||||
}
|
||||
(** The GC parameters are given as a [control] record. *)
|
||||
|
||||
external stat : unit -> stat = "gc_stat"
|
||||
(** Return the current values of the memory management counters in a
|
||||
[stat] record. *)
|
||||
external stat : unit -> stat = "gc_stat"
|
||||
|
||||
external counters : unit -> float * float * float = "gc_counters"
|
||||
(** Return [(minor_words, promoted_words, major_words)]. Much faster
|
||||
than [stat]. *)
|
||||
external counters : unit -> (float * float * float) = "gc_counters"
|
||||
|
||||
(** Return the current values of the GC parameters in a {!Gc.control} record. *)
|
||||
external get : unit -> control = "gc_get"
|
||||
(** Return the current values of the GC parameters in a {!Gc.control} record. *)
|
||||
|
||||
external set : control -> unit = "gc_set"
|
||||
(** [set r] changes the GC parameters according to the {!Gc.control} record [r].
|
||||
The normal usage is:
|
||||
|
||||
[Gc.set { (Gc.get()) with Gc.verbose = 13 }] *)
|
||||
external set : control -> unit = "gc_set"
|
||||
|
||||
(** Trigger a minor collection. *)
|
||||
external minor : unit -> unit = "gc_minor"
|
||||
(** Trigger a minor collection. *)
|
||||
|
||||
(** Finish the current major collection cycle. *)
|
||||
external major : unit -> unit = "gc_major"
|
||||
(** Finish the current major collection cycle. *)
|
||||
|
||||
external full_major : unit -> unit = "gc_full_major"
|
||||
(** Finish the current major collection cycle and perform a complete
|
||||
new cycle. This will collect all currently unreachable blocks. *)
|
||||
external full_major : unit -> unit = "gc_full_major"
|
||||
|
||||
external compact : unit -> unit = "gc_compaction"
|
||||
(** Perform a full major collection and compact the heap. Note that heap
|
||||
compaction is a lengthy operation. *)
|
||||
external compact : unit -> unit = "gc_compaction";;
|
||||
|
||||
val print_stat : out_channel -> unit
|
||||
(** Print the current values of the memory management counters (in
|
||||
human-readable form) into the channel argument. *)
|
||||
val print_stat : out_channel -> unit
|
||||
|
||||
val allocated_bytes : unit -> float
|
||||
(** Return the total number of bytes allocated since the program was
|
||||
started. It is returned as a [float] to avoid overflow problems
|
||||
with [int] on 32-bit machines. *)
|
||||
val allocated_bytes : unit -> float
|
||||
|
||||
val finalise : ('a -> unit) -> 'a -> unit
|
||||
(** [Gc.finalise f v] registers [f] as a finalisation function for [v].
|
||||
[v] must be heap-allocated. [f] will be called with [v] as
|
||||
argument at some point between the first time [v] becomes unreachable
|
||||
|
@ -206,19 +207,18 @@ val allocated_bytes : unit -> float
|
|||
{!Array.make} are guaranteed to be heap-allocated and non-constant
|
||||
except when the length argument is [0].
|
||||
*)
|
||||
val finalise : ('a -> unit) -> 'a -> unit;;
|
||||
|
||||
type alarm
|
||||
(** An alarm is a piece of data that calls a user function at the end of
|
||||
each major GC cycle. The following functions are provided to create
|
||||
and delete alarms. *)
|
||||
type alarm;;
|
||||
|
||||
val create_alarm : (unit -> unit) -> alarm
|
||||
(** [create_alarm f] will arrange for f to be called at the end of each
|
||||
major GC cycle. A value of type {!Gc.alarm} is returned that you can
|
||||
use to call {!Gc.delete_alarm}. *)
|
||||
val create_alarm : (unit -> unit) -> alarm;;
|
||||
|
||||
val delete_alarm : alarm -> unit
|
||||
(** [delete_alarm a] will stop the calls to the function associated
|
||||
to [a]. Calling [delete_alarm a] again has no effect. *)
|
||||
val delete_alarm : alarm -> unit;;
|
||||
|
||||
|
|
|
@ -39,6 +39,13 @@
|
|||
*)
|
||||
|
||||
|
||||
type token =
|
||||
Kwd of string
|
||||
| Ident of string
|
||||
| Int of int
|
||||
| Float of float
|
||||
| String of string
|
||||
| Char of char
|
||||
(** The type of tokens. The lexical classes are: [Int] and [Float]
|
||||
for integer and floating-point numbers; [String] for
|
||||
string literals, enclosed in double quotes; [Char] for
|
||||
|
@ -47,14 +54,8 @@
|
|||
and quotes, or sequences of ``operator characters'' such as
|
||||
[+], [*], etc); and [Kwd] for keywords (either identifiers or
|
||||
single ``special characters'' such as [(], [}], etc). *)
|
||||
type token =
|
||||
Kwd of string
|
||||
| Ident of string
|
||||
| Int of int
|
||||
| Float of float
|
||||
| String of string
|
||||
| Char of char
|
||||
|
||||
val make_lexer : string list -> char Stream.t -> token Stream.t
|
||||
(** Construct the lexer function. The first argument is the list of
|
||||
keywords. An identifier [s] is returned as [Kwd s] if [s]
|
||||
belongs to this list, and as [Ident s] otherwise.
|
||||
|
@ -63,6 +64,5 @@ type token =
|
|||
[Parse_error]) otherwise. Blanks and newlines are skipped.
|
||||
Comments delimited by [(*] and [*)] are skipped as well,
|
||||
and can be nested. *)
|
||||
val make_lexer: string list -> (char Stream.t -> token Stream.t)
|
||||
|
||||
|
||||
|
|
|
@ -21,61 +21,62 @@
|
|||
(** {2 Generic interface} *)
|
||||
|
||||
|
||||
(** The type of hash tables from type ['a] to type ['b]. *)
|
||||
type ('a, 'b) t
|
||||
(** The type of hash tables from type ['a] to type ['b]. *)
|
||||
|
||||
val create : int -> ('a, 'b) t
|
||||
(** [Hashtbl.create n] creates a new, empty hash table, with
|
||||
initial size [n]. For best results, [n] should be on the
|
||||
order of the expected number of elements that will be in
|
||||
the table. The table grows as needed, so [n] is just an
|
||||
initial guess. *)
|
||||
val create : int -> ('a,'b) t
|
||||
|
||||
(** Empty a hash table. *)
|
||||
val clear : ('a, 'b) t -> unit
|
||||
(** Empty a hash table. *)
|
||||
|
||||
val add : ('a, 'b) t -> 'a -> 'b -> unit
|
||||
(** [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 {!Hashtbl.remove}[ tbl x],
|
||||
the previous binding for [x], if any, is restored.
|
||||
(Same behavior as with association lists.) *)
|
||||
val add : ('a, 'b) t -> 'a -> 'b -> unit
|
||||
|
||||
(** Return a copy of the given hashtable. *)
|
||||
val copy : ('a, 'b) t -> ('a, 'b) t
|
||||
(** Return a copy of the given hashtable. *)
|
||||
|
||||
val find : ('a, 'b) t -> 'a -> 'b
|
||||
(** [Hashtbl.find tbl x] returns the current binding of [x] in [tbl],
|
||||
or raises [Not_found] if no such binding exists. *)
|
||||
val find : ('a, 'b) t -> 'a -> 'b
|
||||
|
||||
val find_all : ('a, 'b) t -> 'a -> 'b list
|
||||
(** [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 find_all : ('a, 'b) t -> 'a -> 'b list
|
||||
|
||||
val mem : ('a, 'b) t -> 'a -> bool
|
||||
(** [Hashtbl.mem tbl x] checks if [x] is bound in [tbl]. *)
|
||||
val mem : ('a, 'b) t -> 'a -> bool
|
||||
|
||||
val remove : ('a, 'b) t -> 'a -> unit
|
||||
(** [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 remove : ('a, 'b) t -> 'a -> unit
|
||||
|
||||
val replace : ('a, 'b) t -> 'a -> 'b -> unit
|
||||
(** [Hashtbl.replace tbl x y] replaces the current binding of [x]
|
||||
in [tbl] by a binding of [x] to [y]. If [x] is unbound in [tbl],
|
||||
a binding of [x] to [y] is added to [tbl].
|
||||
This is functionally equivalent to {!Hashtbl.remove}[ tbl x]
|
||||
followed by {!Hashtbl.add}[ tbl x y]. *)
|
||||
val replace : ('a, 'b) t -> 'a -> 'b -> unit
|
||||
|
||||
val iter : ('a -> 'b -> unit) -> ('a, 'b) t -> unit
|
||||
(** [Hashtbl.iter f tbl] applies [f] to all bindings in table [tbl].
|
||||
[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. Each binding is presented exactly once
|
||||
to [f]. *)
|
||||
val iter : ('a -> 'b -> unit) -> ('a, 'b) t -> unit
|
||||
|
||||
val fold : ('a -> 'b -> 'c -> 'c) -> ('a, 'b) t -> 'c -> 'c
|
||||
(** [Hashtbl.fold f tbl init] computes
|
||||
[(f kN dN ... (f k1 d1 init)...)],
|
||||
where [k1 ... kN] are the keys of all bindings in [tbl],
|
||||
|
@ -83,12 +84,13 @@ val iter : ('a -> 'b -> unit) -> ('a, 'b) t -> unit
|
|||
The order in which the bindings are passed to
|
||||
[f] is unspecified. Each binding is presented exactly once
|
||||
to [f]. *)
|
||||
val fold : ('a -> 'b -> 'c -> 'c) -> ('a, 'b) t -> 'c -> 'c
|
||||
|
||||
|
||||
(** {2 Functorial interface} *)
|
||||
|
||||
|
||||
module type HashedType =
|
||||
sig type t val equal : t -> t -> bool val hash : t -> int end
|
||||
(** The input signature of the functor {!Hashtbl.Make}.
|
||||
[t] is the type of keys.
|
||||
[equal] is the equality predicate used to compare keys.
|
||||
|
@ -101,31 +103,26 @@ val fold : ('a -> 'b -> 'c -> 'c) -> ('a, 'b) t -> 'c -> 'c
|
|||
([(=)], {!Hashtbl.hash}) for comparing objects by structure, and
|
||||
([(==)], {!Hashtbl.hash}) for comparing objects by addresses
|
||||
(e.g. for mutable or cyclic keys). *)
|
||||
module type HashedType =
|
||||
sig
|
||||
type t
|
||||
val equal: t -> t -> bool
|
||||
val hash: t -> int
|
||||
end
|
||||
|
||||
|
||||
module type S =
|
||||
sig
|
||||
type key
|
||||
type 'a t
|
||||
val create: int -> 'a t
|
||||
val clear: 'a t -> unit
|
||||
val copy: 'a t -> 'a t
|
||||
val add: 'a t -> key -> 'a -> unit
|
||||
val remove: 'a t -> key -> unit
|
||||
val find: 'a t -> key -> 'a
|
||||
val find_all: 'a t -> key -> 'a list
|
||||
val replace: 'a t -> key -> 'a -> unit
|
||||
val mem: 'a t -> key -> bool
|
||||
val iter: (key -> 'a -> unit) -> 'a t -> unit
|
||||
val fold: (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
|
||||
val create : int -> 'a t
|
||||
val clear : 'a t -> unit
|
||||
val copy : 'a t -> 'a t
|
||||
val add : 'a t -> key -> 'a -> unit
|
||||
val remove : 'a t -> key -> unit
|
||||
val find : 'a t -> key -> 'a
|
||||
val find_all : 'a t -> key -> 'a list
|
||||
val replace : 'a t -> key -> 'a -> unit
|
||||
val mem : 'a t -> key -> bool
|
||||
val iter : (key -> 'a -> unit) -> 'a t -> unit
|
||||
val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
|
||||
end
|
||||
|
||||
module Make (H : HashedType) : S with type key = H.t
|
||||
(** The functor [Hashtbl.Make] returns a structure containing
|
||||
a type [key] of keys and a type ['a t] of hash tables
|
||||
associating data of type ['a] to keys of type [key].
|
||||
|
@ -133,19 +130,19 @@ module type S =
|
|||
interface, but use the hashing and equality functions
|
||||
specified in the functor argument [H] instead of generic
|
||||
equality and hashing. *)
|
||||
module Make (H : HashedType): (S with type key = H.t)
|
||||
|
||||
|
||||
(** {2 The polymorphic hash primitive} *)
|
||||
|
||||
|
||||
val hash : 'a -> int
|
||||
(** [Hashtbl.hash x] associates a positive integer to any value of
|
||||
any type. It is guaranteed that
|
||||
if [x = y], then [hash x = hash y].
|
||||
Moreover, [hash] always terminates, even on cyclic
|
||||
structures. *)
|
||||
val hash : 'a -> int
|
||||
|
||||
external hash_param : int -> int -> 'a -> int = "hash_univ_param" "noalloc"
|
||||
(** [Hashtbl.hash_param n m x] computes a hash value 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
|
||||
|
@ -158,5 +155,4 @@ val hash : 'a -> int
|
|||
value, and therefore collisions are less likely to happen.
|
||||
However, hashing takes longer. The parameters [m] and [n]
|
||||
govern the tradeoff between accuracy and speed. *)
|
||||
external hash_param : int -> int -> 'a -> int = "hash_univ_param" "noalloc"
|
||||
|
||||
|
|
|
@ -25,31 +25,32 @@
|
|||
[int32] are generally slower than those on [int]. Use [int32]
|
||||
only when the application requires exact 32-bit arithmetic. *)
|
||||
|
||||
(** The 32-bit integer 0. *)
|
||||
val zero : int32
|
||||
(** The 32-bit integer 0. *)
|
||||
|
||||
(** The 32-bit integer 1. *)
|
||||
val one : int32
|
||||
(** The 32-bit integer 1. *)
|
||||
|
||||
(** The 32-bit integer -1. *)
|
||||
val minus_one : int32
|
||||
(** The 32-bit integer -1. *)
|
||||
|
||||
(** Unary negation. *)
|
||||
external neg : int32 -> int32 = "%int32_neg"
|
||||
(** Unary negation. *)
|
||||
|
||||
(** Addition. *)
|
||||
external add : int32 -> int32 -> int32 = "%int32_add"
|
||||
(** Addition. *)
|
||||
|
||||
(** Subtraction. *)
|
||||
external sub : int32 -> int32 -> int32 = "%int32_sub"
|
||||
(** Subtraction. *)
|
||||
|
||||
(** Multiplication. *)
|
||||
external mul : int32 -> int32 -> int32 = "%int32_mul"
|
||||
(** Multiplication. *)
|
||||
|
||||
external div : int32 -> int32 -> int32 = "%int32_div"
|
||||
(** Integer division. Raise [Division_by_zero] if the second
|
||||
argument is zero. *)
|
||||
external div : int32 -> int32 -> int32 = "%int32_div"
|
||||
|
||||
external rem : int32 -> int32 -> int32 = "%int32_mod"
|
||||
(** Integer remainder. If [x >= 0] and [y > 0], the result
|
||||
of [Int32.rem x y] satisfies the following properties:
|
||||
[0 <= Int32.rem x y < y] and
|
||||
|
@ -57,87 +58,86 @@ external div : int32 -> int32 -> int32 = "%int32_div"
|
|||
If [y = 0], [Int32.rem x y] raises [Division_by_zero].
|
||||
If [x < 0] or [y < 0], the result of [Int32.rem x y] is
|
||||
not specified and depends on the platform. *)
|
||||
external rem : int32 -> int32 -> int32 = "%int32_mod"
|
||||
|
||||
(** Successor. [Int32.succ x] is [Int32.add x Int32.one]. *)
|
||||
val succ : int32 -> int32
|
||||
(** Successor. [Int32.succ x] is [Int32.add x Int32.one]. *)
|
||||
|
||||
(** Predecessor. [Int32.pred x] is [Int32.sub x Int32.one]. *)
|
||||
val pred : int32 -> int32
|
||||
(** Predecessor. [Int32.pred x] is [Int32.sub x Int32.one]. *)
|
||||
|
||||
(** Return the absolute value of its argument. *)
|
||||
val abs : int32 -> int32
|
||||
(** Return the absolute value of its argument. *)
|
||||
|
||||
(** The greatest representable 32-bit integer, 2{^31} - 1. *)
|
||||
val max_int : int32
|
||||
(** The greatest representable 32-bit integer, 2{^31} - 1. *)
|
||||
|
||||
(** The smallest representable 32-bit integer, -2{^31}. *)
|
||||
val min_int : int32
|
||||
(** The smallest representable 32-bit integer, -2{^31}. *)
|
||||
|
||||
|
||||
(** Bitwise logical and. *)
|
||||
external logand : int32 -> int32 -> int32 = "%int32_and"
|
||||
(** Bitwise logical and. *)
|
||||
|
||||
(** Bitwise logical or. *)
|
||||
external logor : int32 -> int32 -> int32 = "%int32_or"
|
||||
(** Bitwise logical or. *)
|
||||
|
||||
(** Bitwise logical exclusive or. *)
|
||||
external logxor : int32 -> int32 -> int32 = "%int32_xor"
|
||||
(** Bitwise logical exclusive or. *)
|
||||
|
||||
(** Bitwise logical negation *)
|
||||
val lognot : int32 -> int32
|
||||
(** Bitwise logical negation *)
|
||||
|
||||
external shift_left : int32 -> int -> int32 = "%int32_lsl"
|
||||
(** [Int32.shift_left x y] shifts [x] to the left by [y] bits.
|
||||
The result is unspecified if [y < 0] or [y >= 32]. *)
|
||||
external shift_left : int32 -> int -> int32 = "%int32_lsl"
|
||||
|
||||
external shift_right : int32 -> int -> int32 = "%int32_asr"
|
||||
(** [Int32.shift_right x y] shifts [x] to the right by [y] bits.
|
||||
This is an arithmetic shift: the sign bit of [x] is replicated
|
||||
and inserted in the vacated bits.
|
||||
The result is unspecified if [y < 0] or [y >= 32]. *)
|
||||
external shift_right : int32 -> int -> int32 = "%int32_asr"
|
||||
|
||||
external shift_right_logical : int32 -> int -> int32 = "%int32_lsr"
|
||||
(** [Int32.shift_right_logical x y] shifts [x] to the right by [y] bits.
|
||||
This is a logical shift: zeroes are inserted in the vacated bits
|
||||
regardless of the sign of [x].
|
||||
The result is unspecified if [y < 0] or [y >= 32]. *)
|
||||
external shift_right_logical : int32 -> int -> int32 = "%int32_lsr"
|
||||
|
||||
(** Convert the given integer (type [int]) to a 32-bit integer (type [int32]). *)
|
||||
external of_int : int -> int32 = "%int32_of_int"
|
||||
(** Convert the given integer (type [int]) to a 32-bit integer (type [int32]). *)
|
||||
|
||||
external to_int : int32 -> int = "%int32_to_int"
|
||||
(** Convert the given 32-bit integer (type [int32]) to an
|
||||
integer (type [int]). On 32-bit platforms, the 32-bit integer
|
||||
is taken modulo 2{^31}, i.e. the high-order bit is lost
|
||||
during the conversion. On 64-bit platforms, the conversion
|
||||
is exact. *)
|
||||
external to_int : int32 -> int = "%int32_to_int"
|
||||
|
||||
external of_float : float -> int32 = "int32_of_float"
|
||||
(** Convert the given floating-point number to a 32-bit integer,
|
||||
discarding the fractional part (truncate towards 0).
|
||||
The result of the conversion is undefined if, after truncation,
|
||||
the number is outside the range \[{!Int32.min_int}, {!Int32.max_int}\]. *)
|
||||
external of_float : float -> int32 = "int32_of_float"
|
||||
|
||||
(** Convert the given 32-bit integer to a floating-point number. *)
|
||||
external to_float : int32 -> float = "int32_to_float"
|
||||
(** Convert the given 32-bit integer to a floating-point number. *)
|
||||
|
||||
external of_string : string -> int32 = "int32_of_string"
|
||||
(** Convert the given string to a 32-bit 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. *)
|
||||
external of_string : string -> int32 = "int32_of_string"
|
||||
|
||||
(** Return the string representation of its argument, in signed decimal. *)
|
||||
val to_string : int32 -> string
|
||||
(** Return the string representation of its argument, in signed decimal. *)
|
||||
|
||||
external format : string -> int32 -> string = "int32_format"
|
||||
(** [Int32.format fmt n] return the string representation of the
|
||||
32-bit integer [n] in the format specified by [fmt].
|
||||
[fmt] is a [Printf]-style format containing exactly
|
||||
one [%d], [%i], [%u], [%x], [%X] or [%o] conversion specification.
|
||||
This function is deprecated; use {!Printf.sprintf} with a [%lx] format
|
||||
instead. *)
|
||||
external format : string -> int32 -> string = "int32_format"
|
||||
|
||||
|
|
|
@ -31,31 +31,32 @@
|
|||
only when the application requires exact 64-bit arithmetic.
|
||||
*)
|
||||
|
||||
(** The 64-bit integer 0. *)
|
||||
val zero : int64
|
||||
(** The 64-bit integer 0. *)
|
||||
|
||||
(** The 64-bit integer 1. *)
|
||||
val one : int64
|
||||
(** The 64-bit integer 1. *)
|
||||
|
||||
(** The 64-bit integer -1. *)
|
||||
val minus_one : int64
|
||||
(** The 64-bit integer -1. *)
|
||||
|
||||
(** Unary negation. *)
|
||||
external neg : int64 -> int64 = "%int64_neg"
|
||||
(** Unary negation. *)
|
||||
|
||||
(** Addition. *)
|
||||
external add : int64 -> int64 -> int64 = "%int64_add"
|
||||
(** Addition. *)
|
||||
|
||||
(** Subtraction. *)
|
||||
external sub : int64 -> int64 -> int64 = "%int64_sub"
|
||||
(** Subtraction. *)
|
||||
|
||||
(** Multiplication. *)
|
||||
external mul : int64 -> int64 -> int64 = "%int64_mul"
|
||||
(** Multiplication. *)
|
||||
|
||||
external div : int64 -> int64 -> int64 = "%int64_div"
|
||||
(** Integer division. Raise [Division_by_zero] if the second
|
||||
argument is zero. *)
|
||||
external div : int64 -> int64 -> int64 = "%int64_div"
|
||||
|
||||
external rem : int64 -> int64 -> int64 = "%int64_mod"
|
||||
(** Integer remainder. If [x >= 0] and [y > 0], the result
|
||||
of [Int64.rem x y] satisfies the following properties:
|
||||
[0 <= Int64.rem x y < y] and
|
||||
|
@ -63,120 +64,119 @@ external div : int64 -> int64 -> int64 = "%int64_div"
|
|||
If [y = 0], [Int64.rem x y] raises [Division_by_zero].
|
||||
If [x < 0] or [y < 0], the result of [Int64.rem x y] is
|
||||
not specified and depends on the platform. *)
|
||||
external rem : int64 -> int64 -> int64 = "%int64_mod"
|
||||
|
||||
(** Successor. [Int64.succ x] is [Int64.add x Int64.one]. *)
|
||||
val succ : int64 -> int64
|
||||
(** Successor. [Int64.succ x] is [Int64.add x Int64.one]. *)
|
||||
|
||||
(** Predecessor. [Int64.pred x] is [Int64.sub x Int64.one]. *)
|
||||
val pred : int64 -> int64
|
||||
(** Predecessor. [Int64.pred x] is [Int64.sub x Int64.one]. *)
|
||||
|
||||
(** Return the absolute value of its argument. *)
|
||||
val abs : int64 -> int64
|
||||
(** Return the absolute value of its argument. *)
|
||||
|
||||
(** The greatest representable 64-bit integer, 2{^63} - 1. *)
|
||||
val max_int : int64
|
||||
(** The greatest representable 64-bit integer, 2{^63} - 1. *)
|
||||
|
||||
(** The smallest representable 64-bit integer, -2{^63}. *)
|
||||
val min_int : int64
|
||||
(** The smallest representable 64-bit integer, -2{^63}. *)
|
||||
|
||||
(** Bitwise logical and. *)
|
||||
external logand : int64 -> int64 -> int64 = "%int64_and"
|
||||
(** Bitwise logical and. *)
|
||||
|
||||
(** Bitwise logical or. *)
|
||||
external logor : int64 -> int64 -> int64 = "%int64_or"
|
||||
(** Bitwise logical or. *)
|
||||
|
||||
(** Bitwise logical exclusive or. *)
|
||||
external logxor : int64 -> int64 -> int64 = "%int64_xor"
|
||||
(** Bitwise logical exclusive or. *)
|
||||
|
||||
(** Bitwise logical negation *)
|
||||
val lognot : int64 -> int64
|
||||
(** Bitwise logical negation *)
|
||||
|
||||
external shift_left : int64 -> int -> int64 = "%int64_lsl"
|
||||
(** [Int64.shift_left x y] shifts [x] to the left by [y] bits.
|
||||
The result is unspecified if [y < 0] or [y >= 64]. *)
|
||||
external shift_left : int64 -> int -> int64 = "%int64_lsl"
|
||||
|
||||
external shift_right : int64 -> int -> int64 = "%int64_asr"
|
||||
(** [Int64.shift_right x y] shifts [x] to the right by [y] bits.
|
||||
This is an arithmetic shift: the sign bit of [x] is replicated
|
||||
and inserted in the vacated bits.
|
||||
The result is unspecified if [y < 0] or [y >= 64]. *)
|
||||
external shift_right : int64 -> int -> int64 = "%int64_asr"
|
||||
|
||||
external shift_right_logical : int64 -> int -> int64 = "%int64_lsr"
|
||||
(** [Int64.shift_right_logical x y] shifts [x] to the right by [y] bits.
|
||||
This is a logical shift: zeroes are inserted in the vacated bits
|
||||
regardless of the sign of [x].
|
||||
The result is unspecified if [y < 0] or [y >= 64]. *)
|
||||
external shift_right_logical : int64 -> int -> int64 = "%int64_lsr"
|
||||
|
||||
(** Convert the given integer (type [int]) to a 64-bit integer (type [int64]). *)
|
||||
external of_int : int -> int64 = "%int64_of_int"
|
||||
(** Convert the given integer (type [int]) to a 64-bit integer (type [int64]). *)
|
||||
|
||||
external to_int : int64 -> int = "%int64_to_int"
|
||||
(** Convert the given 64-bit integer (type [int64]) to an
|
||||
integer (type [int]). On 64-bit platforms, the 64-bit integer
|
||||
is taken modulo 2{^63}, i.e. the high-order bit is lost
|
||||
during the conversion. On 32-bit platforms, the 64-bit integer
|
||||
is taken modulo 2{^31}, i.e. the top 33 bits are lost
|
||||
during the conversion. *)
|
||||
external to_int : int64 -> int = "%int64_to_int"
|
||||
|
||||
external of_float : float -> int64 = "int64_of_float"
|
||||
(** Convert the given floating-point number to a 64-bit integer,
|
||||
discarding the fractional part (truncate towards 0).
|
||||
The result of the conversion is undefined if, after truncation,
|
||||
the number is outside the range \[{!Int64.min_int}, {!Int64.max_int}\]. *)
|
||||
external of_float : float -> int64 = "int64_of_float"
|
||||
|
||||
(** Convert the given 64-bit integer to a floating-point number. *)
|
||||
external to_float : int64 -> float = "int64_to_float"
|
||||
(** Convert the given 64-bit integer to a floating-point number. *)
|
||||
|
||||
|
||||
external of_int32 : int32 -> int64 = "%int64_of_int32"
|
||||
(** Convert the given 32-bit integer (type [int32])
|
||||
to a 64-bit integer (type [int64]). *)
|
||||
external of_int32 : int32 -> int64 = "%int64_of_int32"
|
||||
|
||||
external to_int32 : int64 -> int32 = "%int64_to_int32"
|
||||
(** Convert the given 64-bit integer (type [int64]) to a
|
||||
32-bit integer (type [int32]). The 64-bit integer
|
||||
is taken modulo 2{^32}, i.e. the top 32 bits are lost
|
||||
during the conversion. *)
|
||||
external to_int32 : int64 -> int32 = "%int64_to_int32"
|
||||
|
||||
external of_nativeint : nativeint -> int64 = "%int64_of_nativeint"
|
||||
(** Convert the given native integer (type [nativeint])
|
||||
to a 64-bit integer (type [int64]). *)
|
||||
external of_nativeint : nativeint -> int64 = "%int64_of_nativeint"
|
||||
|
||||
external to_nativeint : int64 -> nativeint = "%int64_to_nativeint"
|
||||
(** Convert the given 64-bit integer (type [int64]) to a
|
||||
native integer. On 32-bit platforms, the 64-bit integer
|
||||
is taken modulo 2{^32}. On 64-bit platforms,
|
||||
the conversion is exact. *)
|
||||
external to_nativeint : int64 -> nativeint = "%int64_to_nativeint"
|
||||
|
||||
external of_string : string -> int64 = "int64_of_string"
|
||||
(** Convert the given string to a 64-bit 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. *)
|
||||
external of_string : string -> int64 = "int64_of_string"
|
||||
|
||||
(** Return the string representation of its argument, in decimal. *)
|
||||
val to_string : int64 -> string
|
||||
(** Return the string representation of its argument, in decimal. *)
|
||||
|
||||
external format : string -> int64 -> string = "int64_format"
|
||||
(** [Int64.format fmt n] return the string representation of the
|
||||
64-bit integer [n] in the format specified by [fmt].
|
||||
[fmt] is a {!Printf}-style format containing exactly
|
||||
one [%d], [%i], [%u], [%x], [%X] or [%o] conversion specification.
|
||||
This function is deprecated; use {!Printf.sprintf} with a [%Lx] format
|
||||
instead. *)
|
||||
external format : string -> int64 -> string = "int64_format"
|
||||
|
||||
external bits_of_float : float -> int64 = "int64_bits_of_float"
|
||||
(** Return the internal representation of the given float according
|
||||
to the IEEE 754 floating-point ``double format'' bit layout.
|
||||
Bit 63 of the result represents the sign of the float;
|
||||
bits 62 to 52 represent the (biased) exponent; bits 51 to 0
|
||||
represent the mantissa. *)
|
||||
external bits_of_float : float -> int64 = "int64_bits_of_float"
|
||||
|
||||
external float_of_bits : int64 -> float = "int64_float_of_bits"
|
||||
(** Return the floating-point number whose internal representation,
|
||||
according to the IEEE 754 floating-point ``double format'' bit layout,
|
||||
is the given [int64]. *)
|
||||
external float_of_bits : int64 -> float = "int64_float_of_bits"
|
||||
|
||||
|
|
|
@ -14,20 +14,20 @@
|
|||
|
||||
(** Deferred computations. *)
|
||||
|
||||
type 'a status =
|
||||
| Delayed of (unit -> 'a)
|
||||
| Value of 'a
|
||||
type 'a status =
|
||||
Delayed of (unit -> 'a)
|
||||
| Value of 'a
|
||||
| Exception of exn
|
||||
;;
|
||||
|
||||
type 'a t = 'a status ref
|
||||
(** A value of type ['a Lazy.t] is a deferred computation (also called a
|
||||
suspension) that computes a result of type ['a]. The expression
|
||||
[lazy (expr)] returns a suspension that computes [expr]. **)
|
||||
type 'a t = 'a status ref;;
|
||||
|
||||
|
||||
exception Undefined;;
|
||||
exception Undefined
|
||||
|
||||
val force : 'a t -> 'a
|
||||
(** [Lazy.force x] computes the suspension [x] and returns its result.
|
||||
If the suspension was already computed, [Lazy.force x] returns the
|
||||
same value again. If it raised an exception, the same exception is
|
||||
|
@ -35,5 +35,4 @@ exception Undefined;;
|
|||
Raise [Undefined] if the evaluation of the suspension requires its
|
||||
own result.
|
||||
*)
|
||||
val force: 'a t -> 'a;;
|
||||
|
||||
|
|
Loading…
Reference in New Issue