summaryrefslogtreecommitdiffstats
path: root/stdlib/nativeint.mli
blob: 74b50db76121c452a0c911a12601c5ff3ff983a4 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
(***********************************************************************)
(*                                                                     *)
(*                           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    *)
(*  under the terms of the GNU Library General Public License.         *)
(*                                                                     *)
(***********************************************************************)

(* $Id$ *)

(* Module [Nativeint]: processor-native integers *)

(* This module provides operations on the type [nativeint] of
   signed 32-bit integers (on 32-bit platforms) or
   signed 64-bit integers (on 64-bit platforms).
   This integer type has exactly the same width as that of a [long]
   integer type in the C compiler.  All arithmetic operations over
   [nativeint] are taken modulo $2^{32}$ or $2^{64}$ depending
   on the word size of the architecture. *)

val zero: nativeint
val one: nativeint
val minus_one: nativeint
      (* The native integers 0, 1, -1. *)

external neg: nativeint -> nativeint = "%nativeint_neg"
      (* Unary negation. *)
external add: nativeint -> nativeint -> nativeint = "%nativeint_add"
      (* Addition. *)
external sub: nativeint -> nativeint -> nativeint = "%nativeint_sub"
      (* Subtraction. *)
external mul: nativeint -> nativeint -> nativeint = "%nativeint_mul"
      (* Multiplication. *)
external div: nativeint -> nativeint -> nativeint = "%nativeint_div"
      (* Integer division.  Raise [Division_by_zero] if the second 
         argument is zero. *)
external rem: nativeint -> nativeint -> nativeint = "%nativeint_mod"
      (* Integer remainder.  If [x >= 0] and [y > 0], the result
           of [Nativeint.rem x y] satisfies the following properties:
           [0 <= Nativeint.rem x y < y] and
           [x = Nativeint.add (Nativeint.mul (Nativeint.div x y) y) (Nativeint.rem x y)].
           If [y = 0], [Nativeint.rem x y] raises [Division_by_zero].
           If [x < 0] or [y < 0], the result of [Nativeint.rem x y] is
           not specified and depends on the platform. *)
val succ: nativeint -> nativeint
      (* Successor.  [Nativeint.succ x] is [Nativeint.add x 1n]. *)
val pred: nativeint -> nativeint
      (* Predecessor.  [Nativeint.pred x] is [Nativeint.sub x 1n]. *)
val abs: nativeint -> nativeint
      (* Return the absolute value of its argument. *)
val max_int: nativeint
      (* The greatest representable native integer,
         either $2^{31} - 1$ on a 32-bit platform,
         or $2^{63} - 1$ on a 64-bit platform. *)
val min_int: nativeint
      (* The greatest representable native integer,
         either $-2^{31}$ on a 32-bit platform,
         or $-2^{63}$ on a 64-bit platform. *)

external logand: nativeint -> nativeint -> nativeint = "%nativeint_and"
      (* Bitwise logical and. *)
external logor: nativeint -> nativeint -> nativeint = "%nativeint_or"
      (* Bitwise logical or. *)
external logxor: nativeint -> nativeint -> nativeint = "%nativeint_xor"
      (* Bitwise logical exclusive or. *)
val lognot: nativeint -> nativeint
      (* Bitwise logical negation *)
external shift_left: nativeint -> int -> nativeint = "%nativeint_lsl"
      (* [Nativeint.shift_left x y] shifts [x] to the left by [y] bits. *)
external shift_right: nativeint -> int -> nativeint = "%nativeint_asr"
      (* [Nativeint.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. *)
external shift_right_logical: nativeint -> int -> nativeint = "%nativeint_lsr"
      (* [Nativeint.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]. *)

external of_int: int -> nativeint = "%nativeint_of_int"
      (* Convert the given integer (type [int]) to a native integer
         (type [nativeint]). *)
external to_int: nativeint -> int = "%nativeint_to_int"
      (* Convert the given native integer (type [nativeint]) to an
         integer (type [int]).  The high-order bit is lost during
         the conversion. *)

external of_float : float -> nativeint = "nativeint_of_float"
      (* Convert the given floating-point number to a native integer,
         discarding the fractional part (truncate towards 0).
         The result of the conversion is undefined if, after truncation,
         the number is outside the range
         [Nativeint.min_int, Nativeint.max_int]. *)
external to_float : nativeint -> float = "nativeint_to_float"
      (* Convert the given native integer to a floating-point number. *)

external of_int32: int32 -> nativeint = "%nativeint_of_int32"
      (* Convert the given 32-bit integer (type [int32])
         to a native integer. *)
external to_int32: nativeint -> int32 = "%nativeint_to_int32"
      (* Convert the given native integer to a
         32-bit integer (type [int32]).  On 64-bit platforms,
         the 64-bit native integer is taken modulo $2^{32}$,
         i.e. the top 32 bits are lost.  On 32-bit platforms,
         the conversion is exact. *)

external of_string: string -> nativeint = "nativeint_of_string"
      (* Convert the given string to a native 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. *)
val to_string: nativeint -> string
      (* Return the string representation of its argument, in decimal. *)
external format : string -> nativeint -> string = "nativeint_format"
      (* [Nativeint.format fmt n] return the string representation of the
         native 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.
         See the documentation of the [Printf] module for more information, *)