diff options
author | Damien Doligez <damien.doligez-inria.fr> | 2004-01-01 16:42:43 +0000 |
---|---|---|
committer | Damien Doligez <damien.doligez-inria.fr> | 2004-01-01 16:42:43 +0000 |
commit | 5a678d29f58926a5cd7db0c9121c69cb603a77f9 (patch) | |
tree | c8157238e17990d5d90f9eeb1c08506e253593bb /stdlib/int64.mli | |
parent | 331b2d89c3dc4fb7e1b51276a5a9e37a6c8c8b3a (diff) |
depollution suite (PR#1914 et PR#1956)
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@6045 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 82b6a760f..bedfe2c23 100644 --- a/stdlib/int64.mli +++ b/stdlib/int64.mli @@ -114,13 +114,13 @@ external to_int : int64 -> int = "%int64_to_int" is taken modulo 2{^31}, i.e. the top 33 bits are lost during the conversion. *) -external of_float : float -> int64 = "int64_of_float" +external of_float : float -> int64 = "caml_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 to_float : int64 -> float = "int64_to_float" +external to_float : int64 -> float = "caml_int64_to_float" (** Convert the given 64-bit integer to a floating-point number. *) @@ -144,7 +144,7 @@ external to_nativeint : int64 -> nativeint = "%int64_to_nativeint" is taken modulo 2{^32}. On 64-bit platforms, the conversion is exact. *) -external of_string : string -> int64 = "int64_of_string" +external of_string : string -> int64 = "caml_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] @@ -156,14 +156,14 @@ external of_string : string -> int64 = "int64_of_string" val to_string : int64 -> string (** Return the string representation of its argument, in decimal. *) -external bits_of_float : float -> int64 = "int64_bits_of_float" +external bits_of_float : float -> int64 = "caml_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 float_of_bits : int64 -> float = "int64_float_of_bits" +external float_of_bits : int64 -> float = "caml_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]. *) @@ -181,7 +181,7 @@ val compare: t -> t -> int (** {6 Deprecated functions} *) -external format : string -> int64 -> string = "int64_format" +external format : string -> int64 -> string = "caml_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 consisting of exactly one |