Sys.Signals module for a Variant type of signals (and a set_signal function that...
[ocaml.git] / stdlib / int64.mli
blob9ab4e966d0b688f5a051681fd4a712b8be6f3f60
1 (***********************************************************************)
2 (* *)
3 (* Objective Caml *)
4 (* *)
5 (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
6 (* *)
7 (* Copyright 1996 Institut National de Recherche en Informatique et *)
8 (* en Automatique. All rights reserved. This file is distributed *)
9 (* under the terms of the GNU Library General Public License, with *)
10 (* the special exception on linking described in file ../LICENSE. *)
11 (* *)
12 (***********************************************************************)
14 (* $Id$ *)
16 (** 64-bit integers.
18 This module provides operations on the type [int64] of
19 signed 64-bit integers. Unlike the built-in [int] type,
20 the type [int64] is guaranteed to be exactly 64-bit wide on all
21 platforms. All arithmetic operations over [int64] are taken
22 modulo 2{^64}
24 Performance notice: values of type [int64] occupy more memory
25 space than values of type [int], and arithmetic operations on
26 [int64] are generally slower than those on [int]. Use [int64]
27 only when the application requires exact 64-bit arithmetic.
30 val zero : int64
31 (** The 64-bit integer 0. *)
33 val one : int64
34 (** The 64-bit integer 1. *)
36 val minus_one : int64
37 (** The 64-bit integer -1. *)
39 external neg : int64 -> int64 = "%int64_neg"
40 (** Unary negation. *)
42 external add : int64 -> int64 -> int64 = "%int64_add"
43 (** Addition. *)
45 external sub : int64 -> int64 -> int64 = "%int64_sub"
46 (** Subtraction. *)
48 external mul : int64 -> int64 -> int64 = "%int64_mul"
49 (** Multiplication. *)
51 external div : int64 -> int64 -> int64 = "%int64_div"
52 (** Integer division. Raise [Division_by_zero] if the second
53 argument is zero. This division rounds the real quotient of
54 its arguments towards zero, as specified for {!Pervasives.(/)}. *)
56 external rem : int64 -> int64 -> int64 = "%int64_mod"
57 (** Integer remainder. If [y] is not zero, the result
58 of [Int64.rem x y] satisfies the following property:
59 [x = Int64.add (Int64.mul (Int64.div x y) y) (Int64.rem x y)].
60 If [y = 0], [Int64.rem x y] raises [Division_by_zero]. *)
62 val succ : int64 -> int64
63 (** Successor. [Int64.succ x] is [Int64.add x Int64.one]. *)
65 val pred : int64 -> int64
66 (** Predecessor. [Int64.pred x] is [Int64.sub x Int64.one]. *)
68 val abs : int64 -> int64
69 (** Return the absolute value of its argument. *)
71 val max_int : int64
72 (** The greatest representable 64-bit integer, 2{^63} - 1. *)
74 val min_int : int64
75 (** The smallest representable 64-bit integer, -2{^63}. *)
77 external logand : int64 -> int64 -> int64 = "%int64_and"
78 (** Bitwise logical and. *)
80 external logor : int64 -> int64 -> int64 = "%int64_or"
81 (** Bitwise logical or. *)
83 external logxor : int64 -> int64 -> int64 = "%int64_xor"
84 (** Bitwise logical exclusive or. *)
86 val lognot : int64 -> int64
87 (** Bitwise logical negation *)
89 external shift_left : int64 -> int -> int64 = "%int64_lsl"
90 (** [Int64.shift_left x y] shifts [x] to the left by [y] bits.
91 The result is unspecified if [y < 0] or [y >= 64]. *)
93 external shift_right : int64 -> int -> int64 = "%int64_asr"
94 (** [Int64.shift_right x y] shifts [x] to the right by [y] bits.
95 This is an arithmetic shift: the sign bit of [x] is replicated
96 and inserted in the vacated bits.
97 The result is unspecified if [y < 0] or [y >= 64]. *)
99 external shift_right_logical : int64 -> int -> int64 = "%int64_lsr"
100 (** [Int64.shift_right_logical x y] shifts [x] to the right by [y] bits.
101 This is a logical shift: zeroes are inserted in the vacated bits
102 regardless of the sign of [x].
103 The result is unspecified if [y < 0] or [y >= 64]. *)
105 external of_int : int -> int64 = "%int64_of_int"
106 (** Convert the given integer (type [int]) to a 64-bit integer
107 (type [int64]). *)
109 external to_int : int64 -> int = "%int64_to_int"
110 (** Convert the given 64-bit integer (type [int64]) to an
111 integer (type [int]). On 64-bit platforms, the 64-bit integer
112 is taken modulo 2{^63}, i.e. the high-order bit is lost
113 during the conversion. On 32-bit platforms, the 64-bit integer
114 is taken modulo 2{^31}, i.e. the top 33 bits are lost
115 during the conversion. *)
117 external of_float : float -> int64 = "caml_int64_of_float"
118 (** Convert the given floating-point number to a 64-bit integer,
119 discarding the fractional part (truncate towards 0).
120 The result of the conversion is undefined if, after truncation,
121 the number is outside the range \[{!Int64.min_int}, {!Int64.max_int}\]. *)
123 external to_float : int64 -> float = "caml_int64_to_float"
124 (** Convert the given 64-bit integer to a floating-point number. *)
127 external of_int32 : int32 -> int64 = "%int64_of_int32"
128 (** Convert the given 32-bit integer (type [int32])
129 to a 64-bit integer (type [int64]). *)
131 external to_int32 : int64 -> int32 = "%int64_to_int32"
132 (** Convert the given 64-bit integer (type [int64]) to a
133 32-bit integer (type [int32]). The 64-bit integer
134 is taken modulo 2{^32}, i.e. the top 32 bits are lost
135 during the conversion. *)
137 external of_nativeint : nativeint -> int64 = "%int64_of_nativeint"
138 (** Convert the given native integer (type [nativeint])
139 to a 64-bit integer (type [int64]). *)
141 external to_nativeint : int64 -> nativeint = "%int64_to_nativeint"
142 (** Convert the given 64-bit integer (type [int64]) to a
143 native integer. On 32-bit platforms, the 64-bit integer
144 is taken modulo 2{^32}. On 64-bit platforms,
145 the conversion is exact. *)
147 external of_string : string -> int64 = "caml_int64_of_string"
148 (** Convert the given string to a 64-bit integer.
149 The string is read in decimal (by default) or in hexadecimal,
150 octal or binary if the string begins with [0x], [0o] or [0b]
151 respectively.
152 Raise [Failure "int_of_string"] if the given string is not
153 a valid representation of an integer, or if the integer represented
154 exceeds the range of integers representable in type [int64]. *)
156 val to_string : int64 -> string
157 (** Return the string representation of its argument, in decimal. *)
159 external bits_of_float : float -> int64 = "caml_int64_bits_of_float"
160 (** Return the internal representation of the given float according
161 to the IEEE 754 floating-point ``double format'' bit layout.
162 Bit 63 of the result represents the sign of the float;
163 bits 62 to 52 represent the (biased) exponent; bits 51 to 0
164 represent the mantissa. *)
166 external float_of_bits : int64 -> float = "caml_int64_float_of_bits"
167 (** Return the floating-point number whose internal representation,
168 according to the IEEE 754 floating-point ``double format'' bit layout,
169 is the given [int64]. *)
171 type t = int64
172 (** An alias for the type of 64-bit integers. *)
174 val compare: t -> t -> int
175 (** The comparison function for 64-bit integers, with the same specification as
176 {!Pervasives.compare}. Along with the type [t], this function [compare]
177 allows the module [Int64] to be passed as argument to the functors
178 {!Set.Make} and {!Map.Make}. *)
180 val modulo : int64 -> int64 -> int64
181 (** Alias for [Int64.rem] *)
183 val pow : int64 -> int64 -> int64
184 (** [Int64.pow a n] calculates [a] raised to the power of [n] *)
186 (**/**)
188 (** {6 Deprecated functions} *)
190 external format : string -> int64 -> string = "caml_int64_format"
191 (** Do not use this deprecated function. Instead,
192 used {!Printf.sprintf} with a [%L...] format. *)