diff options
author | Damien Doligez <damien.doligez-inria.fr> | 2005-08-13 20:59:37 +0000 |
---|---|---|
committer | Damien Doligez <damien.doligez-inria.fr> | 2005-08-13 20:59:37 +0000 |
commit | a4a3c10e70d755e2382c2eebf5e891582ff79325 (patch) | |
tree | 8b7af748bc36975b07568fc7b2c2ba84d9b7c008 /stdlib/int64.mli | |
parent | f4cc48c8ea61899ee53adb8b635fc228cd13962a (diff) |
fusion des modifs de 3.08.4
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@7019 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/int64.mli')
-rw-r--r-- | stdlib/int64.mli | 12 |
1 files changed, 6 insertions, 6 deletions
diff --git a/stdlib/int64.mli b/stdlib/int64.mli index bedfe2c23..da5f5de1b 100644 --- a/stdlib/int64.mli +++ b/stdlib/int64.mli @@ -19,12 +19,12 @@ signed 64-bit integers. Unlike the built-in [int] type, the type [int64] is guaranteed to be exactly 64-bit wide on all platforms. All arithmetic operations over [int64] are taken - modulo 2{^64} + modulo 2{^64} Performance notice: values of type [int64] occupy more memory space than values of type [int], and arithmetic operations on [int64] are generally slower than those on [int]. Use [int64] - only when the application requires exact 64-bit arithmetic. + only when the application requires exact 64-bit arithmetic. *) val zero : int64 @@ -49,14 +49,13 @@ external mul : int64 -> int64 -> int64 = "%int64_mul" (** Multiplication. *) external div : int64 -> int64 -> int64 = "%int64_div" -(** Integer division. Raise [Division_by_zero] if the second +(** Integer division. Raise [Division_by_zero] if the second argument is zero. This division rounds the real quotient of its arguments towards zero, as specified for {!Pervasives.(/)}. *) external rem : int64 -> int64 -> int64 = "%int64_mod" (** Integer remainder. If [y] is not zero, the result - of [Int64.rem x y] satisfies the following properties: - [Int64.zero <= Int64.rem x y < Int64.abs y] and + of [Int64.rem x y] satisfies the following property: [x = Int64.add (Int64.mul (Int64.div x y) y) (Int64.rem x y)]. If [y = 0], [Int64.rem x y] raises [Division_by_zero]. *) @@ -104,7 +103,8 @@ external shift_right_logical : int64 -> int -> int64 = "%int64_lsr" The result is unspecified if [y < 0] or [y >= 64]. *) external of_int : int -> int64 = "%int64_of_int" -(** Convert the given integer (type [int]) to a 64-bit integer (type [int64]). *) +(** 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 |