Adding @since indications + spacing revision in documentation comments.

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@10546 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Pierre Weis 2010-06-09 10:19:06 +00:00
parent f0588f76fd
commit e873deb417
1 changed files with 15 additions and 11 deletions

View File

@ -52,16 +52,16 @@ external ( = ) : 'a -> 'a -> bool = "%equal"
Equality between cyclic data structures may not terminate. *)
external ( <> ) : 'a -> 'a -> bool = "%notequal"
(** Negation of {!Pervasives.(=)}. *)
(** Negation of {!Pervasives.( = )}. *)
external ( < ) : 'a -> 'a -> bool = "%lessthan"
(** See {!Pervasives.(>=)}. *)
(** See {!Pervasives.( >= )}. *)
external ( > ) : 'a -> 'a -> bool = "%greaterthan"
(** See {!Pervasives.(>=)}. *)
(** See {!Pervasives.( >= )}. *)
external ( <= ) : 'a -> 'a -> bool = "%lessequal"
(** See {!Pervasives.(>=)}. *)
(** See {!Pervasives.( >= )}. *)
external ( >= ) : 'a -> 'a -> bool = "%greaterequal"
(** Structural ordering functions. These functions coincide with
@ -113,7 +113,7 @@ external ( == ) : 'a -> 'a -> bool = "%eq"
[e1 == e2] implies [compare e1 e2 = 0]. *)
external ( != ) : 'a -> 'a -> bool = "%noteq"
(** Negation of {!Pervasives.(==)}. *)
(** Negation of {!Pervasives.( == )}. *)
(** {6 Boolean operations} *)
@ -127,7 +127,7 @@ external ( && ) : bool -> bool -> bool = "%sequand"
[e2] is not evaluated at all. *)
external ( & ) : bool -> bool -> bool = "%sequand"
(** @deprecated {!Pervasives.(&&)} should be used instead. *)
(** @deprecated {!Pervasives.( && )} should be used instead. *)
external ( || ) : bool -> bool -> bool = "%sequor"
(** The boolean ``or''. Evaluation is sequential, left-to-right:
@ -135,7 +135,7 @@ external ( || ) : bool -> bool -> bool = "%sequor"
[e2] is not evaluated at all. *)
external ( or ) : bool -> bool -> bool = "%sequor"
(** @deprecated {!Pervasives.(||)} should be used instead.*)
(** @deprecated {!Pervasives.( || )} should be used instead.*)
(** {6 Integer arithmetic} *)
@ -148,7 +148,9 @@ external ( ~- ) : int -> int = "%negint"
(** Unary negation. You can also write [- e] instead of [~- e]. *)
external ( ~+ ) : int -> int = "%identity"
(** Unary addition. You can also write [+ e] instead of [~+ e]. *)
(** Unary addition. You can also write [+ e] instead of [~+ e].
@since 3.12.0
*)
external succ : int -> int = "%succint"
(** [succ x] is [x + 1]. *)
@ -171,13 +173,13 @@ external ( / ) : int -> int -> int = "%divint"
Integer division rounds the real quotient of its arguments towards zero.
More precisely, if [x >= 0] and [y > 0], [x / y] is the greatest integer
less than or equal to the real quotient of [x] by [y]. Moreover,
[(- x) / y = x / (-y) = - (x / y)]. *)
[(- x) / y = x / (- y) = - (x / y)]. *)
external ( mod ) : int -> int -> int = "%modint"
(** Integer remainder. If [y] is not zero, the result
of [x mod y] satisfies the following properties:
[x = (x / y) * y + x mod y] and
[abs(x mod y) <= abs(y)-1].
[abs(x mod y) <= abs(y) - 1].
If [y = 0], [x mod y] raises [Division_by_zero].
Note that [x mod y] is negative only if [x < 0].
Raise [Division_by_zero] if [y] is zero. *)
@ -243,7 +245,9 @@ external ( ~-. ) : float -> float = "%negfloat"
(** Unary negation. You can also write [-. e] instead of [~-. e]. *)
external ( ~+. ) : float -> float = "%identity"
(** Unary addition. You can also write [+. e] instead of [~+. e]. *)
(** Unary addition. You can also write [+. e] instead of [~+. e].
@since 3.12.0
*)
external ( +. ) : float -> float -> float = "%addfloat"
(** Floating-point addition *)