1 (***********************************************************************)
5 (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
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. *)
12 (***********************************************************************)
16 (** Processor-native integers.
18 This module provides operations on the type [nativeint] of
19 signed 32-bit integers (on 32-bit platforms) or
20 signed 64-bit integers (on 64-bit platforms).
21 This integer type has exactly the same width as that of a [long]
22 integer type in the C compiler. All arithmetic operations over
23 [nativeint] are taken modulo 2{^32} or 2{^64} depending
24 on the word size of the architecture.
26 Performance notice: values of type [nativeint] occupy more memory
27 space than values of type [int], and arithmetic operations on
28 [nativeint] are generally slower than those on [int]. Use [nativeint]
29 only when the application requires the extra bit of precision
34 (** The native integer 0.*)
37 (** The native integer 1.*)
39 val minus_one
: nativeint
40 (** The native integer -1.*)
42 external neg
: nativeint
-> nativeint
= "%nativeint_neg"
43 (** Unary negation. *)
45 external add
: nativeint
-> nativeint
-> nativeint
= "%nativeint_add"
48 external sub
: nativeint
-> nativeint
-> nativeint
= "%nativeint_sub"
51 external mul
: nativeint
-> nativeint
-> nativeint
= "%nativeint_mul"
52 (** Multiplication. *)
54 external div
: nativeint
-> nativeint
-> nativeint
= "%nativeint_div"
55 (** Integer division. Raise [Division_by_zero] if the second
56 argument is zero. This division rounds the real quotient of
57 its arguments towards zero, as specified for {!Pervasives.(/)}. *)
59 external rem
: nativeint
-> nativeint
-> nativeint
= "%nativeint_mod"
60 (** Integer remainder. If [y] is not zero, the result
61 of [Nativeint.rem x y] satisfies the following properties:
62 [Nativeint.zero <= Nativeint.rem x y < Nativeint.abs y] and
63 [x = Nativeint.add (Nativeint.mul (Nativeint.div x y) y) (Nativeint.rem x y)].
64 If [y = 0], [Nativeint.rem x y] raises [Division_by_zero]. *)
66 val succ
: nativeint
-> nativeint
68 [Nativeint.succ x] is [Nativeint.add x Nativeint.one]. *)
70 val pred
: nativeint
-> nativeint
72 [Nativeint.pred x] is [Nativeint.sub x Nativeint.one]. *)
74 val abs
: nativeint
-> nativeint
75 (** Return the absolute value of its argument. *)
78 (** The size in bits of a native integer. This is equal to [32]
79 on a 32-bit platform and to [64] on a 64-bit platform. *)
81 val max_int
: nativeint
82 (** The greatest representable native integer,
83 either 2{^31} - 1 on a 32-bit platform,
84 or 2{^63} - 1 on a 64-bit platform. *)
86 val min_int
: nativeint
87 (** The greatest representable native integer,
88 either -2{^31} on a 32-bit platform,
89 or -2{^63} on a 64-bit platform. *)
91 external logand
: nativeint
-> nativeint
-> nativeint
= "%nativeint_and"
92 (** Bitwise logical and. *)
94 external logor
: nativeint
-> nativeint
-> nativeint
= "%nativeint_or"
95 (** Bitwise logical or. *)
97 external logxor
: nativeint
-> nativeint
-> nativeint
= "%nativeint_xor"
98 (** Bitwise logical exclusive or. *)
100 val lognot
: nativeint
-> nativeint
101 (** Bitwise logical negation *)
103 external shift_left
: nativeint
-> int -> nativeint
= "%nativeint_lsl"
104 (** [Nativeint.shift_left x y] shifts [x] to the left by [y] bits.
105 The result is unspecified if [y < 0] or [y >= bitsize],
106 where [bitsize] is [32] on a 32-bit platform and
107 [64] on a 64-bit platform. *)
109 external shift_right
: nativeint
-> int -> nativeint
= "%nativeint_asr"
110 (** [Nativeint.shift_right x y] shifts [x] to the right by [y] bits.
111 This is an arithmetic shift: the sign bit of [x] is replicated
112 and inserted in the vacated bits.
113 The result is unspecified if [y < 0] or [y >= bitsize]. *)
115 external shift_right_logical
:
116 nativeint
-> int -> nativeint
= "%nativeint_lsr"
117 (** [Nativeint.shift_right_logical x y] shifts [x] to the right
119 This is a logical shift: zeroes are inserted in the vacated bits
120 regardless of the sign of [x].
121 The result is unspecified if [y < 0] or [y >= bitsize]. *)
124 external of_int
: int -> nativeint
= "%nativeint_of_int"
125 (** Convert the given integer (type [int]) to a native integer
126 (type [nativeint]). *)
128 external to_int
: nativeint
-> int = "%nativeint_to_int"
129 (** Convert the given native integer (type [nativeint]) to an
130 integer (type [int]). The high-order bit is lost during
133 external of_float
: float -> nativeint
= "caml_nativeint_of_float"
134 (** Convert the given floating-point number to a native integer,
135 discarding the fractional part (truncate towards 0).
136 The result of the conversion is undefined if, after truncation,
137 the number is outside the range
138 \[{!Nativeint.min_int}, {!Nativeint.max_int}\]. *)
140 external to_float
: nativeint
-> float = "caml_nativeint_to_float"
141 (** Convert the given native integer to a floating-point number. *)
143 external of_int32
: int32
-> nativeint
= "%nativeint_of_int32"
144 (** Convert the given 32-bit integer (type [int32])
145 to a native integer. *)
147 external to_int32
: nativeint
-> int32
= "%nativeint_to_int32"
148 (** Convert the given native integer to a
149 32-bit integer (type [int32]). On 64-bit platforms,
150 the 64-bit native integer is taken modulo 2{^32},
151 i.e. the top 32 bits are lost. On 32-bit platforms,
152 the conversion is exact. *)
154 external of_string
: string -> nativeint
= "caml_nativeint_of_string"
155 (** Convert the given string to a native integer.
156 The string is read in decimal (by default) or in hexadecimal,
157 octal or binary if the string begins with [0x], [0o] or [0b]
159 Raise [Failure "int_of_string"] if the given string is not
160 a valid representation of an integer, or if the integer represented
161 exceeds the range of integers representable in type [nativeint]. *)
163 val to_string
: nativeint
-> string
164 (** Return the string representation of its argument, in decimal. *)
167 (** An alias for the type of native integers. *)
169 val compare
: t
-> t
-> int
170 (** The comparison function for native integers, with the same specification as
171 {!Pervasives.compare}. Along with the type [t], this function [compare]
172 allows the module [Nativeint] to be passed as argument to the functors
173 {!Set.Make} and {!Map.Make}. *)
175 val modulo
: nativeint
-> nativeint
-> nativeint
176 (** Alias for [Nativeint.rem] *)
178 val pow
: nativeint
-> nativeint
-> nativeint
179 (** [Nativeint.pow a n] calculates [a] raised to the power of [n] *)
183 (** {6 Deprecated functions} *)
185 external format
: string -> nativeint
-> string = "caml_nativeint_format"
186 (** [Nativeint.format fmt n] return the string representation of the
187 native integer [n] in the format specified by [fmt].
188 [fmt] is a [Printf]-style format consisting of exactly
189 one [%d], [%i], [%u], [%x], [%X] or [%o] conversion specification.
190 This function is deprecated; use {!Printf.sprintf} with a [%nx] format