2000-02-13 08:44:06 -08:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
|
|
|
(* Objective Caml *)
|
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
2001-12-07 05:41:02 -08:00
|
|
|
(* under the terms of the GNU Library General Public License, with *)
|
|
|
|
(* the special exception on linking described in file ../LICENSE. *)
|
2000-02-13 08:44:06 -08:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
2001-10-29 09:58:08 -08:00
|
|
|
(** 64-bit integers.
|
2000-02-13 08:44:06 -08:00
|
|
|
|
2001-10-26 16:35:44 -07:00
|
|
|
This module provides operations on the type [int64] of
|
2000-02-21 10:14:56 -08:00
|
|
|
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
|
2001-10-29 09:58:08 -08:00
|
|
|
modulo 2{^64}
|
2000-02-13 08:44:06 -08:00
|
|
|
|
2000-02-21 10:14:56 -08:00
|
|
|
The type [int64] is supported on all 64-bit platforms, as well as
|
2000-02-13 08:44:06 -08:00
|
|
|
on all 32-bit platforms for which the C compiler supports 64-bit
|
|
|
|
arithmetic. On 32-bit platforms without support for 64-bit arithmetic,
|
|
|
|
all functions in this module raise an [Invalid_argument] exception.
|
2001-02-05 00:54:18 -08:00
|
|
|
|
|
|
|
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]
|
2001-10-26 15:38:48 -07:00
|
|
|
only when the application requires exact 64-bit arithmetic.
|
|
|
|
*)
|
2000-02-13 08:44:06 -08:00
|
|
|
|
2000-03-21 09:43:25 -08:00
|
|
|
val zero : int64
|
2001-12-03 14:01:28 -08:00
|
|
|
(** The 64-bit integer 0. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2000-03-21 09:43:25 -08:00
|
|
|
val one : int64
|
2001-12-03 14:01:28 -08:00
|
|
|
(** The 64-bit integer 1. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2000-03-21 09:43:25 -08:00
|
|
|
val minus_one : int64
|
2001-12-03 14:01:28 -08:00
|
|
|
(** The 64-bit integer -1. *)
|
2000-02-13 08:44:06 -08:00
|
|
|
|
2000-03-21 09:43:25 -08:00
|
|
|
external neg : int64 -> int64 = "%int64_neg"
|
2001-12-03 14:01:28 -08:00
|
|
|
(** Unary negation. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2000-03-21 09:43:25 -08:00
|
|
|
external add : int64 -> int64 -> int64 = "%int64_add"
|
2001-12-03 14:01:28 -08:00
|
|
|
(** Addition. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2000-03-21 09:43:25 -08:00
|
|
|
external sub : int64 -> int64 -> int64 = "%int64_sub"
|
2001-12-03 14:01:28 -08:00
|
|
|
(** Subtraction. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2000-03-21 09:43:25 -08:00
|
|
|
external mul : int64 -> int64 -> int64 = "%int64_mul"
|
2001-12-03 14:01:28 -08:00
|
|
|
(** Multiplication. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2001-12-03 14:01:28 -08:00
|
|
|
external div : int64 -> int64 -> int64 = "%int64_div"
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Integer division. Raise [Division_by_zero] if the second
|
|
|
|
argument is zero. *)
|
|
|
|
|
2001-12-03 14:01:28 -08:00
|
|
|
external rem : int64 -> int64 -> int64 = "%int64_mod"
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Integer remainder. If [x >= 0] and [y > 0], the result
|
|
|
|
of [Int64.rem x y] satisfies the following properties:
|
|
|
|
[0 <= Int64.rem x y < y] and
|
|
|
|
[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].
|
|
|
|
If [x < 0] or [y < 0], the result of [Int64.rem x y] is
|
|
|
|
not specified and depends on the platform. *)
|
|
|
|
|
2000-03-21 09:43:25 -08:00
|
|
|
val succ : int64 -> int64
|
2001-12-03 14:01:28 -08:00
|
|
|
(** Successor. [Int64.succ x] is [Int64.add x Int64.one]. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2000-03-21 09:43:25 -08:00
|
|
|
val pred : int64 -> int64
|
2001-12-03 14:01:28 -08:00
|
|
|
(** Predecessor. [Int64.pred x] is [Int64.sub x Int64.one]. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2000-03-21 09:43:25 -08:00
|
|
|
val abs : int64 -> int64
|
2001-12-03 14:01:28 -08:00
|
|
|
(** Return the absolute value of its argument. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2000-03-21 09:43:25 -08:00
|
|
|
val max_int : int64
|
2001-12-03 14:01:28 -08:00
|
|
|
(** The greatest representable 64-bit integer, 2{^63} - 1. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2000-03-21 09:43:25 -08:00
|
|
|
val min_int : int64
|
2001-12-03 14:01:28 -08:00
|
|
|
(** The smallest representable 64-bit integer, -2{^63}. *)
|
2000-02-13 08:44:06 -08:00
|
|
|
|
2000-03-21 09:43:25 -08:00
|
|
|
external logand : int64 -> int64 -> int64 = "%int64_and"
|
2001-12-03 14:01:28 -08:00
|
|
|
(** Bitwise logical and. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2000-03-21 09:43:25 -08:00
|
|
|
external logor : int64 -> int64 -> int64 = "%int64_or"
|
2001-12-03 14:01:28 -08:00
|
|
|
(** Bitwise logical or. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2000-03-21 09:43:25 -08:00
|
|
|
external logxor : int64 -> int64 -> int64 = "%int64_xor"
|
2001-12-03 14:01:28 -08:00
|
|
|
(** Bitwise logical exclusive or. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2000-03-21 09:43:25 -08:00
|
|
|
val lognot : int64 -> int64
|
2001-12-03 14:01:28 -08:00
|
|
|
(** Bitwise logical negation *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2001-12-03 14:01:28 -08:00
|
|
|
external shift_left : int64 -> int -> int64 = "%int64_lsl"
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [Int64.shift_left x y] shifts [x] to the left by [y] bits.
|
|
|
|
The result is unspecified if [y < 0] or [y >= 64]. *)
|
|
|
|
|
2001-12-03 14:01:28 -08:00
|
|
|
external shift_right : int64 -> int -> int64 = "%int64_asr"
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [Int64.shift_right x y] shifts [x] to the right by [y] bits.
|
|
|
|
This is an arithmetic shift: the sign bit of [x] is replicated
|
|
|
|
and inserted in the vacated bits.
|
|
|
|
The result is unspecified if [y < 0] or [y >= 64]. *)
|
|
|
|
|
2001-12-03 14:01:28 -08:00
|
|
|
external shift_right_logical : int64 -> int -> int64 = "%int64_lsr"
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [Int64.shift_right_logical x y] shifts [x] to the right by [y] bits.
|
|
|
|
This is a logical shift: zeroes are inserted in the vacated bits
|
|
|
|
regardless of the sign of [x].
|
|
|
|
The result is unspecified if [y < 0] or [y >= 64]. *)
|
2000-02-13 08:44:06 -08:00
|
|
|
|
2000-03-21 09:43:25 -08:00
|
|
|
external of_int : int -> int64 = "%int64_of_int"
|
2001-12-03 14:01:28 -08:00
|
|
|
(** Convert the given integer (type [int]) to a 64-bit integer (type [int64]). *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2001-12-03 14:01:28 -08:00
|
|
|
external to_int : int64 -> int = "%int64_to_int"
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Convert the given 64-bit integer (type [int64]) to an
|
|
|
|
integer (type [int]). On 64-bit platforms, the 64-bit integer
|
2001-10-29 09:58:08 -08:00
|
|
|
is taken modulo 2{^63}, i.e. the high-order bit is lost
|
2001-10-26 15:38:48 -07:00
|
|
|
during the conversion. On 32-bit platforms, the 64-bit integer
|
2001-10-29 09:58:08 -08:00
|
|
|
is taken modulo 2{^31}, i.e. the top 33 bits are lost
|
2001-10-26 15:38:48 -07:00
|
|
|
during the conversion. *)
|
2000-02-13 08:44:06 -08:00
|
|
|
|
2001-12-03 14:01:28 -08:00
|
|
|
external of_float : float -> int64 = "int64_of_float"
|
2001-10-26 15:38:48 -07:00
|
|
|
(** 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,
|
2001-10-29 09:58:08 -08:00
|
|
|
the number is outside the range \[{!Int64.min_int}, {!Int64.max_int}\]. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2000-04-18 01:51:28 -07:00
|
|
|
external to_float : int64 -> float = "int64_to_float"
|
2001-12-03 14:01:28 -08:00
|
|
|
(** Convert the given 64-bit integer to a floating-point number. *)
|
2000-04-18 01:51:28 -07:00
|
|
|
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2001-12-03 14:01:28 -08:00
|
|
|
external of_int32 : int32 -> int64 = "%int64_of_int32"
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Convert the given 32-bit integer (type [int32])
|
|
|
|
to a 64-bit integer (type [int64]). *)
|
|
|
|
|
2001-12-03 14:01:28 -08:00
|
|
|
external to_int32 : int64 -> int32 = "%int64_to_int32"
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Convert the given 64-bit integer (type [int64]) to a
|
|
|
|
32-bit integer (type [int32]). The 64-bit integer
|
2001-10-29 09:58:08 -08:00
|
|
|
is taken modulo 2{^32}, i.e. the top 32 bits are lost
|
2001-10-26 15:38:48 -07:00
|
|
|
during the conversion. *)
|
2000-02-13 08:44:06 -08:00
|
|
|
|
2001-12-03 14:01:28 -08:00
|
|
|
external of_nativeint : nativeint -> int64 = "%int64_of_nativeint"
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Convert the given native integer (type [nativeint])
|
|
|
|
to a 64-bit integer (type [int64]). *)
|
|
|
|
|
2001-12-03 14:01:28 -08:00
|
|
|
external to_nativeint : int64 -> nativeint = "%int64_to_nativeint"
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Convert the given 64-bit integer (type [int64]) to a
|
|
|
|
native integer. On 32-bit platforms, the 64-bit integer
|
2001-10-29 09:58:08 -08:00
|
|
|
is taken modulo 2{^32}. On 64-bit platforms,
|
2001-10-26 15:38:48 -07:00
|
|
|
the conversion is exact. *)
|
2000-03-05 11:17:54 -08:00
|
|
|
|
2001-12-03 14:01:28 -08:00
|
|
|
external of_string : string -> int64 = "int64_of_string"
|
2001-10-26 15:38:48 -07:00
|
|
|
(** 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]
|
|
|
|
respectively.
|
|
|
|
Raise [Failure "int_of_string"] if the given string is not
|
|
|
|
a valid representation of an integer. *)
|
|
|
|
|
2000-03-21 09:43:25 -08:00
|
|
|
val to_string : int64 -> string
|
2001-12-03 14:01:28 -08:00
|
|
|
(** Return the string representation of its argument, in decimal. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2001-12-03 14:01:28 -08:00
|
|
|
external format : string -> int64 -> string = "int64_format"
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [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 containing exactly
|
|
|
|
one [%d], [%i], [%u], [%x], [%X] or [%o] conversion specification.
|
2001-10-30 06:32:37 -08:00
|
|
|
This function is deprecated; use {!Printf.sprintf} with a [%Lx] format
|
|
|
|
instead. *)
|
2001-02-05 00:54:18 -08:00
|
|
|
|
2001-12-03 14:01:28 -08:00
|
|
|
external bits_of_float : float -> int64 = "int64_bits_of_float"
|
2001-10-26 15:38:48 -07:00
|
|
|
(** 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. *)
|
|
|
|
|
2001-12-03 14:01:28 -08:00
|
|
|
external float_of_bits : int64 -> float = "int64_float_of_bits"
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Return the floating-point number whose internal representation,
|
|
|
|
according to the IEEE 754 floating-point ``double format'' bit layout,
|
|
|
|
is the given [int64]. *)
|
|
|
|
|