Modification emplacements et syntaxe commentaires pour OCamldoc.

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@3927 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Maxence Guesdon 2001-10-26 23:33:00 +00:00
parent b95796f461
commit 241f51d429
10 changed files with 444 additions and 337 deletions

View File

@ -24,7 +24,7 @@
(** The input signature of the functor [Map.Make].
[t] is the type of the map keys.
{!Pervasives.compare} is a total ordering function over the 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],

View File

@ -12,10 +12,10 @@
(* $Id$ *)
(* Module [StdLabels]: standard labeled libraries *)
(** Standard labeled libraries.
(* This meta-module provides labelized version of the [Hashtbl],
[Map] and [Set] modules.
This meta-module provides labelized version of the {!Hashtbl},
{!Map} and {!Set} modules.
They only differ by their labels. They are provided for backwards
compatibility with previous versions of Objective Caml, and it is

View File

@ -12,106 +12,133 @@
(* $Id$ *)
(* Module [Set]: sets over ordered types *)
(** Sets over ordered types.
(* This module implements the set data structure, given a total ordering
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. *)
logarithmic in the size of the set, for instance.
*)
(** 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].
Example: a suitable ordering function is
the generic structural comparison function {!Pervasives.compare}. *)
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].
Example: a suitable ordering function is
the generic structural comparison function [compare]. *)
module type S =
sig
(** The type of the set elements. *)
type elt
(* The type of the set elements. *)
(** The type of sets. *)
type t
(* The type of sets. *)
(** The empty set. *)
val empty: t
(* The empty set. *)
(** Test whether a set is empty or not. *)
val is_empty: t -> bool
(* Test whether a set is empty or not. *)
(** [mem x s] tests whether [x] belongs to the set [s]. *)
val mem: elt -> t -> bool
(* [mem x s] tests whether [x] belongs to the set [s]. *)
(** [add x s] returns a set containing all elements of [s],
plus [x]. If [x] was already in [s], [s] is returned unchanged. *)
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. *)
(** [singleton x] returns the one-element set containing only [x]. *)
val singleton: elt -> t
(* [singleton x] returns the one-element set containing only [x]. *)
(** [remove x s] returns a set containing all elements of [s],
except [x]. If [x] was not 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. *)
(** Set union. *)
val union: t -> t -> t
(** Set interseection. *)
val inter: t -> t -> t
(** Set difference. *)
val diff: t -> t -> t
(* Union, intersection and set difference. *)
(** Total ordering between sets. Can be used as the ordering function
for doing sets of sets. *)
val compare: t -> t -> int
(* Total ordering between sets. Can be used as the ordering function
for doing sets of sets. *)
(** [equal s1 s2] tests whether the sets [s1] and [s2] are
equal, that is, contain equal elements. *)
val equal: t -> t -> bool
(* [equal s1 s2] tests whether the sets [s1] and [s2] are
equal, that is, contain equal elements. *)
(** [subset s1 s2] tests whether the set [s1] is a subset of
the set [s2]. *)
val subset: t -> t -> bool
(* [subset s1 s2] tests whether the set [s1] is a subset of
the set [s2]. *)
(** [iter f s] applies [f] in turn to all elements of [s].
The order in which the elements of [s] are presented to [f]
is unspecified. *)
val iter: (elt -> unit) -> t -> unit
(* [iter f s] applies [f] in turn to all elements of [s].
The order in which the elements of [s] are presented to [f]
is unspecified. *)
(** [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
unspecified. *)
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
unspecified. *)
(** [for_all p s] checks if all elements of the set
satisfy the predicate [p]. *)
val for_all: (elt -> bool) -> t -> bool
(* [for_all p s] checks if all elements of the set
satisfy the predicate [p]. *)
(** [exists p s] checks if at least one element of
the set satisfies the predicate [p]. *)
val exists: (elt -> bool) -> t -> bool
(* [exists p s] checks if at least one element of
the set satisfies the predicate [p]. *)
(** [filter p s] returns the set of all elements in [s]
that satisfy predicate [p]. *)
val filter: (elt -> bool) -> t -> t
(* [filter p s] returns the set of all elements in [s]
that satisfy predicate [p]. *)
(** [partition p s] returns a pair of sets [(s1, s2)], where
[s1] is the set of all the elements of [s] that satisfy the
predicate [p], and [s2] is the set of all the elements of
[s] that do not satisfy [p]. *)
val partition: (elt -> bool) -> t -> t * t
(* [partition p s] returns a pair of sets [(s1, s2)], where
[s1] is the set of all the elements of [s] that satisfy the
predicate [p], and [s2] is the set of all the elements of
[s] that do not satisfy [p]. *)
(** Return the number of elements of a set. *)
val cardinal: t -> int
(* Return the number of elements of a set. *)
(** Return the list of all elements of the given set.
The returned list is sorted in increasing order with respect
to the ordering [Ord.compare], where [Ord] is the argument
given to {!Set.Make}. *)
val elements: t -> elt list
(* Return the list of all elements of the given set.
The returned list is sorted in increasing order with respect
to the ordering [Ord.compare], where [Ord] is the argument
given to [Set.Make]. *)
(** Return the smallest element of the given set
(with respect to the [Ord.compare] ordering), or raise
[Not_found] if the set is empty. *)
val min_elt: t -> elt
(* Return the smallest element of the given set
(with respect to the [Ord.compare] ordering), or raise
[Not_found] if the set is empty. *)
(** Same as {!Set.S.min_elt}, but returns the largest element of the
given set. *)
val max_elt: t -> elt
(* Same as [min_elt], but returns the largest element of the
given set. *)
(** Return one element of the given set, or raise [Not_found] if
the set is empty. Which element is chosen is unspecified,
but equal elements will be chosen for equal sets. *)
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 unspecified,
but equal elements will be chosen for equal sets. *)
end
module Make(Ord: OrderedType): (S with type elt = Ord.t)
(* Functor building an implementation of the set structure
(** Functor building an implementation of the set structure
given a totally ordered type. *)
module Make (Ord : OrderedType): (S with type elt = Ord.t)

View File

@ -12,28 +12,29 @@
(* $Id$ *)
(* Module [Sort]: sorting and merging lists *)
(** Sorting and merging lists.
(* This module is obsolete and exists only for backward compatibility.
The sorting functions in [Array] and [List] should be used instead.
@deprecated This module is obsolete and exists only for backward compatibility.
The sorting functions in {!Array} and {!List} should be used instead.
The new functions are faster and use less memory.
*)
(** Sort a list in increasing order according to an ordering predicate.
The predicate should return [true] if its first argument is
less than or equal to its second argument. *)
val list : ('a -> 'a -> bool) -> 'a list -> 'a list
(* Sort a list in increasing order according to an ordering predicate.
The predicate should return [true] if its first argument is
less than or equal to its second argument. *)
(** Sort an array in increasing order according to an
ordering predicate.
The predicate should return [true] if its first argument is
less than or equal to its second argument.
The array is sorted in place. *)
val array : ('a -> 'a -> bool) -> 'a array -> unit
(* Sort an array in increasing order according to an
ordering predicate.
The predicate should return [true] if its first argument is
less than or equal to its second argument.
The array is sorted in place. *)
(** Merge two lists according to the given predicate.
Assuming the two argument lists are sorted according to the
predicate, [merge] returns a sorted list containing the elements
from the two lists. The behavior is undefined if the two
argument lists were not sorted. *)
val merge : ('a -> 'a -> bool) -> 'a list -> 'a list -> 'a list
(* Merge two lists according to the given predicate.
Assuming the two argument lists are sorted according to the
predicate, [merge] returns a sorted list containing the elements
from the two lists. The behavior is undefined if the two
argument lists were not sorted. *)

View File

@ -12,33 +12,43 @@
(* $Id$ *)
(* Module [Stack]: last-in first-out stacks *)
(** Last-in first-out stacks.
(* This module implements stacks (LIFOs), with in-place modification. *)
This module implements stacks (LIFOs), with in-place modification.
*)
(** The type of stacks containing elements of type ['a]. *)
type 'a t
(* The type of stacks containing elements of type ['a]. *)
(** Raised when {!Stack.pop} or {!Stack.top} is applied to an empty stack. *)
exception Empty
(* Raised when [pop] is applied to an empty stack. *)
(** Return a new stack, initially empty. *)
val create: unit -> 'a t
(* Return a new stack, initially empty. *)
(** [push x s] adds the element [x] at the top of stack [s]. *)
val push: 'a -> 'a t -> unit
(* [push x s] adds the element [x] at the top of stack [s]. *)
(** [pop s] removes and returns the topmost element in stack [s],
or raises [Empty] if the stack is empty. *)
val pop: 'a t -> 'a
(* [pop s] removes and returns the topmost element in stack [s],
or raises [Empty] if the stack is empty. *)
(** [top s] returns the topmost element in stack [s],
or raises [Empty] if the stack is empty. *)
val top: 'a t -> 'a
(* [top s] returns the topmost element in stack [s],
or raises [Empty] if the stack is empty. *)
(** Discard all elements from a stack. *)
val clear: 'a t -> unit
(* Discard all elements from a stack. *)
(** Return a copy of the given stack. *)
val copy: 'a t -> 'a t
(* Return a copy of the given stack. *)
(** Return the number of elements in a stack. *)
val length: 'a t -> int
(* Return the number of elements in a 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. *)
val iter: ('a -> unit) -> '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
bottom of the stack. The stack itself is unchanged. *)

View File

@ -12,10 +12,10 @@
(* $Id$ *)
(* Module [StdLabels]: standard labeled libraries *)
(** Standard labeled libraries.
(* This meta-module provides labelized version of the [Array],
[List] and [String] modules.
This meta-module provides labelized version of the {!Array},
{!List} and {!String} modules.
They only differ by their labels. Detailed interfaces can be found
in [arrayLabels.mli], [listLabels.mli] and [stringLabels.mli].

View File

@ -12,71 +12,84 @@
(* $Id$ *)
(* Module [Stream]: streams and parsers *)
(** Streams and parsers. *)
(** The type of streams holding values of type ['a]. *)
type 'a t
(* The type of streams holding values of type ['a]. *)
(** Raised by parsers when none of the first components of the stream
patterns is accepted. *)
exception Failure;;
(* Raised by parsers when none of the first components of the stream
patterns is accepted. *)
(** Raised by parsers when the first component of a stream pattern is
accepted, but one of the following components is rejected. *)
exception Error of string;;
(* Raised by parsers when the first component of a stream pattern is
accepted, but one of the following components is rejected. *)
(** Stream builders *)
(* Warning: these functions create streams with fast access; it is illegal
(** {2 Stream builders}
Warning: these functions create streams with fast access; it is illegal
to mix them with streams built with [[< >]]; would raise [Failure]
when accessing such mixed streams. *)
when accessing such mixed streams.
*)
(** [Stream.from f] returns a stream built from the function [f].
To create a new stream element, the function [f] is called with
the current stream count. The user function [f] must return either
[Some <value>] for a value or [None] to specify the end of the
stream. *)
val from : (int -> 'a option) -> 'a t;;
(* [Stream.from f] returns a stream built from the function [f].
To create a new stream element, the function [f] is called with
the current stream count. The user function [f] must return either
[Some <value>] for a value or [None] to specify the end of the
stream. *)
(** Return the stream holding the elements of the list in the same
order. *)
val of_list : 'a list -> 'a t;;
(* Return the stream holding the elements of the list in the same
order. *)
(** Return the stream of the characters of the string parameter. *)
val of_string : string -> char t;;
(* Return the stream of the characters of the string parameter. *)
(** Return the stream of the characters read from the input channel. *)
val of_channel : in_channel -> char t;;
(* Return the stream of the characters read from the input channel. *)
(** Stream iterator *)
(** {2 Stream iterator} *)
(** [Stream.iter f s] scans the whole stream s, applying function [f]
in turn to each stream element encountered. *)
val iter : ('a -> unit) -> 'a t -> unit;;
(* [Stream.iter f s] scans the whole stream s, applying function [f]
in turn to each stream element encountered. *)
(** Predefined parsers *)
(** {2 Predefined parsers} *)
(** Return the first element of the stream and remove it from the
stream. Raise Stream.Failure if the stream is empty. *)
val next : 'a t -> 'a;;
(* Return the first element of the stream and remove it from the
stream. Raise [Stream.Failure] if the stream is empty. *)
(** Return [()] if the stream is empty, else raise [Stream.Failure]. *)
val empty : 'a t -> unit;;
(* Return [()] if the stream is empty, else raise [Stream.Failure]. *)
(** Useful functions *)
(** {2 Useful functions} *)
(** Return [Some] of "the first element" of the stream, or [None] if
the stream is empty. *)
val peek : 'a t -> 'a option;;
(* Return [Some] of "the first element" of the stream, or [None] if
the stream is empty. *)
val junk : 'a t -> unit;;
(* Remove the first element of the stream, possibly unfreezing
it before. *)
val count : 'a t -> int;;
(* Return the current count of the stream elements, i.e. the number
of the stream elements discarded. *)
(** Remove the first element of the stream, possibly unfreezing
it before. *)
val junk : 'a t -> unit;;
(** Return the current count of the stream elements, i.e. the number
of the stream elements discarded. *)
val count : 'a t -> int;;
(** [npeek n] returns the list of the [n] first elements of
the stream, or all its remaining elements if less than [n]
elements are available. *)
val npeek : int -> 'a t -> 'a list;;
(* [npeek n] returns the list of the [n] first elements of
the stream, or all its remaining elements if less than [n]
elements are available. *)
(*--*)
(*** For system use only, not for the casual user *)
(** {2 For system use only, not for the casual user} *)
val iapp : 'a t -> 'a t -> 'a t;;
val icons : 'a -> 'a t -> 'a t;;

View File

@ -12,120 +12,135 @@
(* $Id$ *)
(* Module [String]: string operations *)
(** String operations. *)
(** Return the length (number of characters) of the given string. *)
external length : string -> int = "%string_length"
(* Return the length (number of characters) of the given string. *)
(** [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 outside the range
0 to [(String.length s - 1)].
You can also write [s.[n]] instead of [String.get s n]. *)
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 outside the range
0 to [(String.length s - 1)].
You can also write [s.[n]] instead of [String.get s n]. *)
(** [String.set s n c] modifies string [s] in place,
replacing the character number [n] by [c].
Raise [Invalid_argument] if [n] is outside the range
0 to [(String.length s - 1)].
You can also write [s.[n] <- c] instead of [String.set s n c]. *)
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 outside the range
0 to [(String.length s - 1)].
You can also write [s.[n] <- c] instead of [String.set s n c]. *)
(** [String.create n] returns a fresh string of length [n].
The string initially contains arbitrary characters.
Raise [Invalid_argument] if [n < 0] or [n > Sys.max_string_length].
*)
external create : int -> string = "create_string"
(* [String.create n] returns a fresh string of length [n].
The string initially contains arbitrary characters.
Raise [Invalid_argument] if [n < 0] or [n > Sys.max_string_length].
*)
(** [String.make n c] returns a fresh string of length [n],
filled with the character [c].
Raise [Invalid_argument] if [n < 0] or [n > ]{!Sys.max_string_length}.*)
val make : int -> char -> string
(* [String.make n c] returns a fresh string of length [n],
filled with the character [c].
Raise [Invalid_argument] if [n < 0] or [n > Sys.max_string_length].
*)
(** Return a copy of the given string. *)
val copy : string -> string
(* Return a copy of the given 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 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]. *)
(** [String.fill 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 fill : string -> int -> int -> char -> unit
(* [String.fill 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]. *)
(** [String.blit src srcoff dst dstoff len] copies [len] characters
from string [src], starting at character number [srcoff], to
string [dst], starting at character number [dstoff]. It works
correctly even if [src] and [dst] are the same string,
and the source and destination chunks overlap.
Raise [Invalid_argument] if [srcoff] and [len] do not
designate a valid substring of [src], or if [dstoff] and [len]
do not designate a valid substring of [dst]. *)
val blit : string -> int -> string -> int -> int -> unit
(* [String.blit src srcoff dst dstoff len] copies [len] characters
from string [src], starting at character number [srcoff], to
string [dst], starting at character number [dstoff]. It works
correctly even if [src] and [dst] are the same string,
and the source and destination chunks overlap.
Raise [Invalid_argument] if [srcoff] and [len] do not
designate a valid substring of [src], or if [dstoff] and [len]
do not designate a valid substring of [dst]. *)
(** [String.concat sep sl] catenates the list of strings [sl],
inserting the separator string [sep] between each. *)
val concat : string -> string list -> string
(* [String.concat sep sl] catenates the list of strings [sl],
inserting the separator string [sep] between each. *)
(** [String.iter f s] applies function [f] in turn to all
the characters of [s]. It is equivalent to
[f s.(0); f s.(1); ...; f s.(String.length s - 1); ()]. *)
val iter : (char -> unit) -> string -> unit
(* [String.iter f s] applies function [f] in turn to all
the characters of [s]. It is equivalent to
[f s.(0); f s.(1); ...; f s.(String.length s - 1); ()]. *)
(** Return a copy of the argument, with special characters
represented by escape sequences, following the lexical
conventions of Objective Caml. If there is no special
character in the argument, return the original string itself,
not a copy. *)
val escaped: string -> string
(* Return a copy of the argument, with special characters
represented by escape sequences, following the lexical
conventions of Objective Caml. If there is no special
character in the argument, return the original string itself,
not a copy. *)
(** [String.index s c] returns the position of the leftmost
occurrence of character [c] in string [s].
Raise [Not_found] if [c] does not occur in [s]. *)
val index: string -> char -> int
(* [String.index s c] returns the position of the leftmost
occurrence of character [c] in string [s].
Raise [Not_found] if [c] does not occur in [s]. *)
(** [String.rindex s c] returns the position of the rightmost
occurrence of character [c] in string [s].
Raise [Not_found] if [c] does not occur in [s]. *)
val rindex: string -> char -> int
(* [String.rindex s c] returns the position of the rightmost
occurrence of character [c] in string [s].
Raise [Not_found] if [c] does not occur in [s]. *)
(** Same as {!String.index}, but start
searching at the character position given as second argument.
[String.index s c] is equivalent to [String.index_from s 0 c].*)
val index_from: string -> int -> char -> int
(** Same as {!String.rindex}, but start
searching at the character position given as second argument.
[String.rindex s c] is equivalent to
[String.rindex_from s (String.length s - 1) c]. *)
val rindex_from: string -> int -> char -> int
(* Same as [String.index] and [String.rindex], but start
searching at the character position given as second argument.
[String.index s c] is equivalent to [String.index_from s 0 c],
and [String.rindex s c] to
[String.rindex_from s (String.length s - 1) c]. *)
(** [String.contains s c] tests if character [c]
appears in the string [s]. *)
val contains : string -> char -> bool
(* [String.contains s c] tests if character [c]
appears in the string [s]. *)
val contains_from : string -> int -> char -> bool
(* [String.contains_from s start c] tests if character [c]
appears in the substring of [s] starting from [start] to the end
of [s].
Raise [Invalid_argument] if [start] is not a valid index of [s]. *)
val rcontains_from : string -> int -> char -> bool
(* [String.rcontains_from s stop c] tests if character [c]
appears in the substring of [s] starting from the beginning
of [s] to index [stop].
Raise [Invalid_argument] if [stop] is not a valid index of [s]. *)
(** [String.contains_from s start c] tests if character [c]
appears in the substring of [s] starting from [start] to the end
of [s].
Raise [Invalid_argument] if [start] is not a valid index of [s]. *)
val contains_from : string -> int -> char -> bool
(** [String.rcontains_from s stop c] tests if character [c]
appears in the substring of [s] starting from the beginning
of [s] to index [stop].
Raise [Invalid_argument] if [stop] is not a valid index of [s]. *)
val rcontains_from : string -> int -> char -> bool
(** Return a copy of the argument, with all lowercase letters
translated to uppercase, including accented letters of the ISO
Latin-1 (8859-1) character set. *)
val uppercase: string -> string
(* Return a copy of the argument, with all lowercase letters
translated to uppercase, including accented letters of the ISO
Latin-1 (8859-1) character set. *)
(** Return a copy of the argument, with all uppercase letters
translated to lowercase, including accented letters of the ISO
Latin-1 (8859-1) character set. *)
val lowercase: string -> string
(* Return a copy of the argument, with all uppercase letters
translated to lowercase, including accented letters of the ISO
Latin-1 (8859-1) character set. *)
(** Return a copy of the argument, with the first letter set to uppercase. *)
val capitalize: string -> string
(* Return a copy of the argument, with the first letter
set to uppercase. *)
(** Return a copy of the argument, with the first letter set to lowercase. *)
val uncapitalize: string -> string
(* Return a copy of the argument, with the first letter
set to lowercase. *)
(*--*)

View File

@ -12,98 +12,140 @@
(* $Id$ *)
(* Module [Sys]: system interface *)
(** System interface. *)
(** 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 command-line arguments
given to the program. *)
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 command-line arguments
given to the program. *)
(** Test if a file with the given name exists. *)
external file_exists: string -> bool = "sys_file_exists"
(* Test if a file with the given name exists. *)
(** Remove the given file name from the file system. *)
external remove: string -> unit = "sys_remove"
(* Remove the given file name from the file system. *)
(** Rename a file. The first argument is the old name and the
second is the new name. *)
external rename: string -> string -> unit = "sys_rename"
(* Rename a file. The first argument is the old name and the
second is the new name. *)
(** Return the value associated to a variable in the process
environment. Raise [Not_found] if the variable is unbound. *)
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. *)
(** Execute the given shell command and return its exit code. *)
external command: string -> int = "sys_system_command"
(* Execute the given shell command and return its exit code. *)
(** Return the processor time, in seconds, used by the program
since the beginning of execution. *)
external time: unit -> float = "sys_time"
(* Return the processor time, in seconds, used by the program
since the beginning of execution. *)
(** Change the current working directory of the process. *)
external chdir: string -> unit = "sys_chdir"
(* Change the current working directory of the process. *)
(** Return the current working directory of the process. *)
external getcwd: unit -> string = "sys_getcwd"
(* Return the current working directory of the process. *)
(** This reference is initially set to [false] in standalone
programs and to [true] if the code is being executed under
the interactive toplevel system [ocaml]. *)
val interactive: bool ref
(* This reference is initially set to [false] in standalone
programs and to [true] if the code is being executed under
the interactive toplevel system [ocaml]. *)
(** Operating system currently executing the Caml program.
One of ["Unix"], ["Win32"], ["Cygwin"] or ["MacOS"]. *)
val os_type: string
(* Operating system currently executing the Caml program.
One of ["Unix"], ["Win32"], ["Cygwin"] or ["MacOS"]. *)
(** Size of one word on the machine currently executing the Caml
program, in bits: 32 or 64. *)
val word_size: int
(* Size of one word on the machine currently executing the Caml
program, in bits: 32 or 64. *)
(** Maximum length of a string. *)
val max_string_length: int
(* Maximum length of a string. *)
(** Maximum length of an array. *)
val max_array_length: int
(* Maximum length of an array. *)
(*** Signal handling *)
(** {2 Signal handling} *)
(** What to do when receiving a signal:
- [Signal_default]: take the default behavior
(usually: abort the program)
- [Signal_ignore]: ignore the signal
- [Signal_handle f]: call function [f], giving it the signal
number as argument. *)
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
(usually: abort the program)
- [Signal_ignore]: ignore the signal
- [Signal_handle f]: call function [f], giving it the signal
number as argument. *)
(** Set the behavior of the system on receipt of a given signal.
The first argument is the signal number. Return the behavior
previously associated with the signal. *)
external signal: int -> signal_behavior -> signal_behavior
= "install_signal_handler"
(* Set the behavior of the system on receipt of a given signal.
The first argument is the signal number. Return the behavior
previously associated with the signal. *)
(** Same as {!Sys.signal} but return value is ignored. *)
val set_signal: int -> signal_behavior -> unit
(* Same as [signal] but return value is ignored. *)
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 *)
val sigvtalrm: int (* Timeout in virtual time *)
val sigprof: int (* Profiling interrupt *)
(* Signal numbers for the standard POSIX signals. *)
(** {3 Signal numbers for the standard POSIX signals.} *)
(** Abnormal termination *)
val sigabrt: int
(** Timeout *)
val sigalrm: int
(** Arithmetic exception *)
val sigfpe: int
(** Hangup on controlling terminal *)
val sighup: int
(** Invalid hardware instruction *)
val sigill: int
(** Interactive interrupt (ctrl-C) *)
val sigint: int
(** Termination (cannot be ignored) *)
val sigkill: int
(** Broken pipe *)
val sigpipe: int
(** Interactive termination *)
val sigquit: int
(** Invalid memory reference *)
val sigsegv: int
(** Termination *)
val sigterm: int
(** Application-defined signal 1 *)
val sigusr1: int
(** Application-defined signal 2 *)
val sigusr2: int
(** Child process terminated *)
val sigchld: int
(** Continue *)
val sigcont: int
(** Stop *)
val sigstop: int
(** Interactive stop *)
val sigtstp: int
(** Terminal read from background process *)
val sigttin: int
(** Terminal write from background process *)
val sigttou: int
(** Timeout in virtual time *)
val sigvtalrm: int
(** Profiling interrupt *)
val sigprof: int
(** Exception raised on interactive interrupt if {!Sys.catch_break}
is on. *)
exception Break
(* Exception raised on interactive interrupt if [catch_break]
is on. *)
(** [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. *)
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. *)

View File

@ -12,66 +12,65 @@
(* $Id$ *)
(* Module [Weak]: arrays of weak pointers *)
(** Arrays of weak pointers. *)
(** The type of arrays of weak pointers (weak arrays). A weak
pointer is a value that the garbage collector may erase at
any time.
A weak pointer is said to be full if it points to a value,
empty if the value was erased by the GC.*)
type 'a t;;
(* The type of arrays of weak pointers (weak arrays). A weak
pointer is a value that the garbage collector may erase at
any time.
A weak pointer is said to be full if it points to a value,
empty if the value was erased by the GC.
*)
(** [Weak.create n] returns a new weak array of length [n].
All the pointers are initially empty. Raise [Invalid_argument]
if [n] is negative or greater than {!Sys.max_array_length}[-1].*)
val create : int -> 'a t;;
(* [Weak.create n] returns a new weak array of length [n].
All the pointers are initially empty. Raise [Invalid_argument]
if [n] is negative or greater than [Sys.max_array_length-1].
*)
(** [Weak.length ar] returns the length (number of elements) of
[ar].*)
val length : 'a t -> int;;
(* [Weak.length ar] returns the length (number of elements) of
[ar].
*)
(** [Weak.set ar n (Some el)] sets the [n]th cell of [ar] to be a
(full) pointer to [el]; [Weak.set ar n None] sets the [n]th
cell of [ar] to empty.
Raise [Invalid_argument "Weak.set"] if [n] is not in the range
0 to {!Weak.length}[ a - 1].*)
val set : 'a t -> int -> 'a option -> unit;;
(* [Weak.set ar n (Some el)] sets the [n]th cell of [ar] to be a
(full) pointer to [el]; [Weak.set ar n None] sets the [n]th
cell of [ar] to empty.
Raise [Invalid_argument "Weak.set"] if [n] is not in the range
0 to [Weak.length a - 1].
*)
(** [Weak.get ar n] returns None if the [n]th cell of [ar] is
empty, [Some x] (where [x] is the value) if it is full.
Raise [Invalid_argument "Weak.get"] if [n] is not in the range
0 to {!Weak.length}[ a - 1].*)
val get : 'a t -> int -> 'a option;;
(* [Weak.get ar n] returns None if the [n]th cell of [ar] is
empty, [Some x] (where [x] is the value) if it is full.
Raise [Invalid_argument "Weak.get"] if [n] is not in the range
0 to [Weak.length a - 1].
*)
(** [Weak.get_copy ar n] returns None if the [n]th cell of [ar] is
empty, [Some x] (where [x] is a (shallow) copy of the value) if
it is full.
In addition to pitfalls with mutable values, the interesting
difference with [get] is that [get_copy] does not prevent
the incremental GC from erasing the value in its current cycle
([get] may delay the erasure to the next GC cycle).
Raise [Invalid_argument "Weak.get"] if [n] is not in the range
0 to {!Weak.length}[ a - 1].*)
val get_copy : 'a t -> int -> 'a option;;
(* [Weak.get_copy ar n] returns None if the [n]th cell of [ar] is
empty, [Some x] (where [x] is a (shallow) copy of the value) if
it is full.
In addition to pitfalls with mutable values, the interesting
difference with [get] is that [get_copy] does not prevent
the incremental GC from erasing the value in its current cycle
([get] may delay the erasure to the next GC cycle).
Raise [Invalid_argument "Weak.get"] if [n] is not in the range
0 to [Weak.length a - 1].
*)
(** [Weak.check ar n] returns [true] if the [n]th cell of [ar] is
full, [false] if it is empty. Note that even if [Weak.check ar n]
returns [true], a subsequent {!Weak.get}[ ar n] can return [None].*)
val check: 'a t -> int -> bool;;
(* [Weak.check ar n] returns [true] if the [n]th cell of [ar] is
full, [false] if it is empty. Note that even if [Weak.check ar n]
returns [true], a subsequent [Weak.get ar n] can return [None].
*)
(** [Weak.fill ar ofs len el] sets to [el] all pointers of [ar] from
[ofs] to [ofs + len - 1]. Raise [Invalid_argument "Weak.fill"]
if [ofs] and [len] do not designate a valid subarray of [a].*)
val fill: 'a t -> int -> int -> 'a option -> unit;;
(* [Weak.fill ar ofs len el] sets to [el] all pointers of [ar] from
[ofs] to [ofs + len - 1]. Raise [Invalid_argument "Weak.fill"]
if [ofs] and [len] do not designate a valid subarray of [a].
*)
(** [Weak.blit ar1 off1 ar2 off2 len] copies [len] weak pointers
from [ar1] (starting at [off1]) to [ar2] (starting at [off2]).
It works correctly even if [ar1] and [ar2] are the same.
Raise [Invalid_argument "Weak.blit"] if [off1] and [len] do
not designate a valid subarray of [ar1], or if [off2] and [len]
do not designate a valid subarray of [ar2].*)
val blit : 'a t -> int -> 'a t -> int -> int -> unit;;
(* [Weak.blit ar1 off1 ar2 off2 len] copies [len] weak pointers
from [ar1] (starting at [off1]) to [ar2] (starting at [off2]).
It works correctly even if [ar1] and [ar2] are the same.
Raise [Invalid_argument "Weak.blit"] if [off1] and [len] do
not designate a valid subarray of [ar1], or if [off2] and [len]
do not designate a valid subarray of [ar2].
*)