MAJ documentation:

- comportement de nan avec les comparaisons et avec la fonction compare
- exceptions levees par les acces hors-bornes
- exceptions de debordement dans les conversions string -> int


git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@5963 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Xavier Leroy 2003-11-21 16:06:08 +00:00
parent f009490d09
commit 6c5d5d9e03
9 changed files with 55 additions and 32 deletions

View File

@ -22,18 +22,18 @@ 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].
You can also write [a.(n)] instead of [Array.get a n].
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]. *)
Raise [Invalid_argument "index out of bounds"]
if [n] is outside the range 0 to [(Array.length a - 1)]. *)
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].
You can also write [a.(n) <- x] instead of [Array.set a n 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]. *)
Raise [Invalid_argument "index out of bounds"]
if [n] is outside the range 0 to [Array.length a - 1]. *)
external make : int -> 'a -> 'a array = "make_vect"
(** [Array.make n x] returns a fresh array of length [n],

View File

@ -106,7 +106,10 @@ module type HashedType =
as computed by [hash].
Examples: suitable ([equal], [hash]) pairs for arbitrary key
types include
([(=)], {!Hashtbl.hash}) for comparing objects by structure, and
([(=)], {!Hashtbl.hash}) for comparing objects by structure,
([(fun x y -> compare x y = 0)], {!Hashtbl.hash})
for comparing objects by structure and handling {!Pervasives.nan}
correctly, and
([(==)], {!Hashtbl.hash}) for comparing objects by addresses
(e.g. for mutable or cyclic keys). *)
end
@ -147,7 +150,7 @@ module Make (H : HashedType) : S with type key = H.t
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].
if [x = y] or [Pervasives.compare x y = 0], then [hash x = hash y].
Moreover, [hash] always terminates, even on cyclic
structures. *)

View File

@ -128,7 +128,8 @@ external of_string : string -> int32 = "int32_of_string"
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. *)
a valid representation of an integer, or if the integer represented
exceeds the range of integers representable in type [int32]. *)
val to_string : int32 -> string
(** Return the string representation of its argument, in signed decimal. *)

View File

@ -150,7 +150,8 @@ external of_string : string -> int64 = "int64_of_string"
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. *)
a valid representation of an integer, or if the integer represented
exceeds the range of integers representable in type [int64]. *)
val to_string : int64 -> string
(** Return the string representation of its argument, in decimal. *)

View File

@ -242,8 +242,7 @@ val sort : ('a -> 'a -> int) -> 'a list -> 'a list
compare as equal, a positive integer if the first is greater,
and a negative integer if the first is smaller (see Array.sort for
a complete specification). For example,
{!Pervasives.compare} is a suitable comparison function, provided
there are no floating-point NaN values in the data.
{!Pervasives.compare} is a suitable comparison function.
The resulting list is sorted in increasing order.
[List.sort] is guaranteed to run in constant heap space
(in addition to the size of the result list) and logarithmic

View File

@ -34,8 +34,7 @@ module type OrderedType =
[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}, provided there are
no floating-point NaN values in the data. *)
comparison function {!Pervasives.compare}. *)
end
(** Input signature of the functor {!Map.Make}. *)

View File

@ -157,7 +157,8 @@ external of_string : string -> nativeint = "nativeint_of_string"
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. *)
a valid representation of an integer, or if the integer represented
exceeds the range of integers representable in type [nativeint]. *)
val to_string : nativeint -> string
(** Return the string representation of its argument, in decimal. *)

View File

@ -48,8 +48,8 @@ external ( = ) : 'a -> 'a -> bool = "%equal"
Mutable structures (e.g. references and arrays) are equal
if and only if their current contents are structurally equal,
even if the two mutable objects are not the same physical object.
Equality between functional values may raise [Invalid_argument].
Equality between cyclic data structures may not terminate. *)
Equality between functional values raises [Invalid_argument].
Equality between cyclic data structures does not terminate. *)
external ( <> ) : 'a -> 'a -> bool = "%notequal"
(** Negation of {!Pervasives.(=)}. *)
@ -70,14 +70,27 @@ external ( >= ) : 'a -> 'a -> bool = "%greaterequal"
total ordering over all types.
The ordering is compatible with [(=)]. As in the case
of [(=)], mutable structures are compared by contents.
Comparison between functional values may raise [Invalid_argument].
Comparison between cyclic structures may not terminate. *)
Comparison between functional values raises [Invalid_argument].
Comparison between cyclic structures does not terminate. *)
external compare : 'a -> 'a -> int = "%compare"
(** [compare x y] returns [0] if [x=y], a negative integer if
[x<y], and a positive integer if [x>y]. The same restrictions
as for [=] apply. [compare] can be used as the comparison function
required by the {!Set.Make} and {!Map.Make} functors. *)
(** [compare x y] returns [0] if [x] is equal to [y],
a negative integer if [x] is less than [y], and a positive integer
if [x] is greater than [y]. The ordering implemented by [compare]
is compatible with the comparison predicates [=], [<] and [>]
defined above, with one difference on the treatment of the float value
{!Pervasives.nan}. Namely, the comparison predicates treat [nan]
as different from any other float value, including itself;
while [compare] treats [nan] as equal to itself and less than any
other float value. This treatment of [nan] ensures that [compare]
defines a total ordering relation.
[compare] applied to functional values may raise [Invalid_argument].
[compare] applied to cyclic structures may not terminate.
The [compare] function can be used as the comparison function
required by the {!Set.Make} and {!Map.Make} functors, as well as
the {!List.sort} and {!Array.sort} functions. *)
val min : 'a -> 'a -> 'a
(** Return the smaller of the two arguments. *)
@ -92,7 +105,7 @@ external ( == ) : 'a -> 'a -> bool = "%eq"
physical modification of [e1] also affects [e2].
On non-mutable structures, the behavior of [(==)] is
implementation-dependent; however, it is guaranteed that
[e1 == e2] implies [e1 = e2]. *)
[e1 == e2] implies [compare e1 e2 = 0]. *)
external ( != ) : 'a -> 'a -> bool = "%noteq"
(** Negation of {!Pervasives.(==)}. *)
@ -334,7 +347,10 @@ val neg_infinity : float
val nan : float
(** A special floating-point value denoting the result of an
undefined operation such as [0.0 /. 0.0]. Stands for
``not a number''. *)
``not a number''. Any floating-point operation with [nan] as
argument returns [nan] as result. As for floating-point comparisons,
[=], [<], [<=], [>] and [>=] return [false] and [<>] returns [true]
if one or both of their arguments is [nan]. *)
val max_float : float
(** The largest positive finite value of type [float]. *)
@ -412,7 +428,8 @@ external int_of_string : string -> int = "int_of_string"
begins with [0x] or [0X]), octal (if it begins with [0o] or [0O]),
or binary (if it begins with [0b] or [0B]).
Raise [Failure "int_of_string"] if the given string is not
a valid representation of an integer. *)
a valid representation of an integer, or if the integer represented
exceeds the range of integers representable in type [int]. *)
val string_of_float : float -> string
(** Return the string representation of a floating-point number. *)

View File

@ -22,16 +22,18 @@ 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]. *)
You can also write [s.[n]] instead of [String.get s n].
Raise [Invalid_argument "index out of bounds"]
if [n] is outside the range 0 to [(String.length s - 1)]. *)
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]. *)
You can also write [s.[n] <- c] instead of [String.set s n c].
Raise [Invalid_argument "index out of bounds"]
if [n] is outside the range 0 to [(String.length s - 1)]. *)
external create : int -> string = "create_string"
(** [String.create n] returns a fresh string of length [n].