Source file int_intf.ml

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
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
(** An interface to use for int-like types, e.g., {{!Base.Int}[Int]} and
    {{!Base.Int64}[Int64]}. *)

open! Import

module type Round = sig
  type t

  (** [round] rounds an int to a multiple of a given [to_multiple_of] argument, according
      to a direction [dir], with default [dir] being [`Nearest]. [round] will raise if
      [to_multiple_of <= 0]. If the result overflows (too far positive or too far
      negative), [round] returns an incorrect result.

      {v
       | `Down    | rounds toward Int.neg_infinity                          |
       | `Up      | rounds toward Int.infinity                              |
       | `Nearest | rounds to the nearest multiple, or `Up in case of a tie |
       | `Zero    | rounds toward zero                                      |
     v}

      Here are some examples for [round ~to_multiple_of:10] for each direction:

      {v
       | `Down    | {10 .. 19} --> 10 | { 0 ... 9} --> 0 | {-10 ... -1} --> -10 |
       | `Up      | { 1 .. 10} --> 10 | {-9 ... 0} --> 0 | {-19 .. -10} --> -10 |
       | `Zero    | {10 .. 19} --> 10 | {-9 ... 9} --> 0 | {-19 .. -10} --> -10 |
       | `Nearest | { 5 .. 14} --> 10 | {-5 ... 4} --> 0 | {-15 ... -6} --> -10 |
     v}

      For convenience and performance, there are variants of [round] with [dir]
      hard-coded. If you are writing performance-critical code you should use these. *)

  val round : ?dir:[ `Zero | `Nearest | `Up | `Down ] -> t -> to_multiple_of:t -> t
  val round_towards_zero : t -> to_multiple_of:t -> t
  val round_down : t -> to_multiple_of:t -> t
  val round_up : t -> to_multiple_of:t -> t
  val round_nearest : t -> to_multiple_of:t -> t
end

(** String format for integers, [to_string] / [sexp_of_t] direction only. Includes
    comparisons and hash functions for [[@@deriving]]. *)
module type To_string_format = sig
  type t [@@deriving_inline sexp_of, compare ~localize, hash]

  val sexp_of_t : t -> Sexplib0.Sexp.t

  include Ppx_compare_lib.Comparable.S with type t := t
  include Ppx_compare_lib.Comparable.S_local with type t := t
  include Ppx_hash_lib.Hashable.S with type t := t

  [@@@end]

  val to_string : t -> string
  val to_string_hum : ?delimiter:char -> t -> string
end

(** String format for integers, including both [to_string] / [sexp_of_t] and [of_string] /
    [t_of_sexp] directions. Includes comparisons and hash functions for [[@@deriving]]. *)
module type String_format = sig
  type t [@@deriving_inline sexp, sexp_grammar, compare ~localize, hash]

  include Sexplib0.Sexpable.S with type t := t

  val t_sexp_grammar : t Sexplib0.Sexp_grammar.t

  include Ppx_compare_lib.Comparable.S with type t := t
  include Ppx_compare_lib.Comparable.S_local with type t := t
  include Ppx_hash_lib.Hashable.S with type t := t

  [@@@end]

  include Stringable.S with type t := t

  val to_string_hum : ?delimiter:char -> t -> string
end

(** Binary format for integers, unsigned and starting with [0b]. *)
module type Binaryable = sig
  type t

  module Binary : To_string_format with type t = t
end

(** Hex format for integers, signed and starting with [0x]. *)
module type Hexable = sig
  type t

  module Hex : String_format with type t = t
end

module type S_common = sig
  type t [@@deriving_inline sexp, sexp_grammar]

  include Sexplib0.Sexpable.S with type t := t

  val t_sexp_grammar : t Sexplib0.Sexp_grammar.t

  [@@@end]

  include Floatable.S with type t := t
  include Intable.S with type t := t
  include Identifiable.S with type t := t
  include Comparable.With_zero with type t := t
  include Ppx_compare_lib.Comparable.S_local with type t := t
  include Ppx_compare_lib.Equal.S_local with type t := t
  include Invariant.S with type t := t
  include Hexable with type t := t
  include Binaryable with type t := t

  val of_string_opt : string -> t option

  (** [delimiter] is an underscore by default. *)
  val to_string_hum : ?delimiter:char -> t -> string

  (** {2 Infix operators and constants} *)

  val zero : t
  val one : t
  val minus_one : t
  val ( + ) : t -> t -> t
  val ( - ) : t -> t -> t
  val ( * ) : t -> t -> t

  (** Integer exponentiation *)
  val ( ** ) : t -> t -> t

  (** Negation *)

  val neg : t -> t
  val ( ~- ) : t -> t

  (** There are two pairs of integer division and remainder functions, [/%] and [%], and
      [/] and [rem].  They both satisfy the same equation relating the quotient and the
      remainder:

      {[
        x = (x /% y) * y + (x % y);
        x = (x /  y) * y + (rem x y);
      ]}

      The functions return the same values if [x] and [y] are positive.  They all raise
      if [y = 0].

      The functions differ if [x < 0] or [y < 0].

      If [y < 0], then [%] and [/%] raise, whereas [/] and [rem] do not.

      [x % y] always returns a value between 0 and [y - 1], even when [x < 0].  On the
      other hand, [rem x y] returns a negative value if and only if [x < 0]; that value
      satisfies [abs (rem x y) <= abs y - 1]. *)

  val ( /% ) : t -> t -> t
  val ( % ) : t -> t -> t
  val ( / ) : t -> t -> t
  val rem : t -> t -> t

  (** Float division of integers. *)
  val ( // ) : t -> t -> float

  (** Same as [bit_and]. *)
  val ( land ) : t -> t -> t

  (** Same as [bit_or]. *)
  val ( lor ) : t -> t -> t

  (** Same as [bit_xor]. *)
  val ( lxor ) : t -> t -> t

  (** Same as [bit_not]. *)
  val lnot : t -> t

  (** Same as [shift_left]. *)
  val ( lsl ) : t -> int -> t

  (** Same as [shift_right]. *)
  val ( asr ) : t -> int -> t

  (** {2 Other common functions} *)

  include Round with type t := t

  (** Returns the absolute value of the argument.  May be negative if the input is
      [min_value]. *)
  val abs : t -> t

  (** {2 Successor and predecessor functions} *)

  val succ : t -> t
  val pred : t -> t

  (** {2 Exponentiation} *)

  (** [pow base exponent] returns [base] raised to the power of [exponent].  It is OK if
      [base <= 0].  [pow] raises if [exponent < 0], or an integer overflow would occur. *)
  val pow : t -> t -> t

  (** {2 Bit-wise logical operations } *)

  (** These are identical to [land], [lor], etc. except they're not infix and have
      different names. *)
  val bit_and : t -> t -> t

  val bit_or : t -> t -> t
  val bit_xor : t -> t -> t
  val bit_not : t -> t

  (** Returns the number of 1 bits in the binary representation of the input. *)
  val popcount : t -> int

  (** {2 Bit-shifting operations }

      The results are unspecified for negative shifts and shifts [>= num_bits]. *)

  (** Shifts left, filling in with zeroes. *)
  val shift_left : t -> int -> t

  (** Shifts right, preserving the sign of the input. *)
  val shift_right : t -> int -> t

  (** {2 Increment and decrement functions for integer references } *)

  val decr : t ref -> unit
  val incr : t ref -> unit

  (** {2 Conversion functions to related integer types} *)

  val of_int32_exn : int32 -> t
  val to_int32_exn : t -> int32
  val of_int64_exn : int64 -> t
  val to_int64 : t -> int64
  val of_nativeint_exn : nativeint -> t
  val to_nativeint_exn : t -> nativeint

  (** [of_float_unchecked] truncates the given floating point number to an integer,
      rounding towards zero.
      The result is unspecified if the argument is nan or falls outside the range
      of representable integers. *)
  val of_float_unchecked : float -> t
end

module type Operators_unbounded = sig
  type t

  val ( + ) : t -> t -> t
  val ( - ) : t -> t -> t
  val ( * ) : t -> t -> t
  val ( / ) : t -> t -> t
  val ( ~- ) : t -> t
  val ( ** ) : t -> t -> t

  include Comparisons.Infix with type t := t

  val abs : t -> t
  val neg : t -> t
  val zero : t
  val ( % ) : t -> t -> t
  val ( /% ) : t -> t -> t
  val ( // ) : t -> t -> float
  val ( land ) : t -> t -> t
  val ( lor ) : t -> t -> t
  val ( lxor ) : t -> t -> t
  val lnot : t -> t
  val ( lsl ) : t -> int -> t
  val ( asr ) : t -> int -> t
end

module type Operators = sig
  include Operators_unbounded

  val ( lsr ) : t -> int -> t
end

(** [S_unbounded] is a generic interface for unbounded integers, e.g. [Bignum.Bigint].
    [S_unbounded] is a restriction of [S] (below) that omits values that depend on
    fixed-size integers. *)
module type S_unbounded = sig
  include S_common (** @inline *)

  (** A sub-module designed to be opened to make working with ints more convenient.  *)
  module O : Operators_unbounded with type t := t
end

(** [S] is a generic interface for fixed-size integers. *)
module type S = sig
  include S_common (** @inline *)

  (** The number of bits available in this integer type.  Note that the integer
      representations are signed. *)
  val num_bits : int

  (** The largest representable integer. *)
  val max_value : t

  (** The smallest representable integer. *)
  val min_value : t

  (** Same as [shift_right_logical]. *)
  val ( lsr ) : t -> int -> t

  (** Shifts right, filling in with zeroes, which will not preserve the sign of the
      input. *)
  val shift_right_logical : t -> int -> t

  (** [ceil_pow2 x] returns the smallest power of 2 that is greater than or equal to [x].
      The implementation may only be called for [x > 0].  Example: [ceil_pow2 17 = 32] *)
  val ceil_pow2 : t -> t

  (** [floor_pow2 x] returns the largest power of 2 that is less than or equal to [x]. The
      implementation may only be called for [x > 0].  Example: [floor_pow2 17 = 16] *)
  val floor_pow2 : t -> t

  (** [ceil_log2 x] returns the ceiling of log-base-2 of [x], and raises if [x <= 0]. *)
  val ceil_log2 : t -> int

  (** [floor_log2 x] returns the floor of log-base-2 of [x], and raises if [x <= 0]. *)
  val floor_log2 : t -> int

  (** [is_pow2 x] returns true iff [x] is a power of 2.  [is_pow2] raises if [x <= 0]. *)
  val is_pow2 : t -> bool

  (** Returns the number of leading zeros in the binary representation of the input, as an
      integer between 0 and one less than [num_bits].

      The results are unspecified for [t = 0]. *)
  val clz : t -> int

  (** Returns the number of trailing zeros in the binary representation of the input, as
      an integer between 0 and one less than [num_bits].

      The results are unspecified for [t = 0]. *)
  val ctz : t -> int

  (** A sub-module designed to be opened to make working with ints more convenient.  *)
  module O : Operators with type t := t
end

module type Int_without_module_types = sig
  (** OCaml's native integer type.

      The number of bits in an integer is platform dependent, being 31-bits on a 32-bit
      platform, and 63-bits on a 64-bit platform.  [int] is a signed integer type.  [int]s
      are also subject to overflow, meaning that [Int.max_value + 1 = Int.min_value].

      [int]s always fit in a machine word. *)

  type t = int [@@deriving_inline globalize]

  val globalize : t -> t

  [@@@end]

  include S with type t := t (** @inline *)

  module O : sig
    (*_ Declared as externals so that the compiler skips the caml_apply_X wrapping even
      when compiling without cross library inlining. *)
    external ( + ) : (t[@local_opt]) -> (t[@local_opt]) -> t = "%addint"
    external ( - ) : (t[@local_opt]) -> (t[@local_opt]) -> t = "%subint"
    external ( * ) : (t[@local_opt]) -> (t[@local_opt]) -> t = "%mulint"
    external ( / ) : (t[@local_opt]) -> (t[@local_opt]) -> t = "%divint"
    external ( ~- ) : (t[@local_opt]) -> t = "%negint"
    val ( ** ) : t -> t -> t
    external ( = ) : (t[@local_opt]) -> (t[@local_opt]) -> bool = "%equal"
    external ( <> ) : (t[@local_opt]) -> (t[@local_opt]) -> bool = "%notequal"
    external ( < ) : (t[@local_opt]) -> (t[@local_opt]) -> bool = "%lessthan"
    external ( > ) : (t[@local_opt]) -> (t[@local_opt]) -> bool = "%greaterthan"
    external ( <= ) : (t[@local_opt]) -> (t[@local_opt]) -> bool = "%lessequal"
    external ( >= ) : (t[@local_opt]) -> (t[@local_opt]) -> bool = "%greaterequal"
    external ( land ) : (t[@local_opt]) -> (t[@local_opt]) -> t = "%andint"
    external ( lor ) : (t[@local_opt]) -> (t[@local_opt]) -> t = "%orint"
    external ( lxor ) : (t[@local_opt]) -> (t[@local_opt]) -> t = "%xorint"
    val lnot : t -> t
    val abs : t -> t
    external neg : (t[@local_opt]) -> t = "%negint"
    val zero : t
    val ( % ) : t -> t -> t
    val ( /% ) : t -> t -> t
    val ( // ) : t -> t -> float
    external ( lsl ) : (t[@local_opt]) -> (int[@local_opt]) -> t = "%lslint"
    external ( asr ) : (t[@local_opt]) -> (int[@local_opt]) -> t = "%asrint"
    external ( lsr ) : (t[@local_opt]) -> (int[@local_opt]) -> t = "%lsrint"
  end

  include module type of O

  (** [max_value_30_bits = 2^30 - 1].  It is useful for writing tests that work on both
      64-bit and 32-bit platforms. *)
  val max_value_30_bits : t

  (** {2 Conversion functions} *)

  val of_int : int -> t
  val to_int : t -> int
  val of_int32 : int32 -> t option
  val to_int32 : t -> int32 option
  val of_int64 : int64 -> t option
  val of_nativeint : nativeint -> t option
  val to_nativeint : t -> nativeint

  (** {3 Truncating conversions}

      These functions return the least-significant bits of the input. In cases
      where optional conversions return [Some x], truncating conversions return [x]. *)

  (*_ Declared as externals so that the compiler skips the caml_apply_X wrapping even when
    compiling without cross library inlining. *)
  external to_int32_trunc : (t[@local_opt]) -> (int32[@local_opt]) = "%int32_of_int"
  external of_int32_trunc : (int32[@local_opt]) -> t = "%int32_to_int"
  external of_int64_trunc : (int64[@local_opt]) -> t = "%int64_to_int"
  external of_nativeint_trunc : (nativeint[@local_opt]) -> t = "%nativeint_to_int"

  (** {2 Byte swap operations}

      Byte swap operations reverse the order of bytes in an integer. For
      example, {!Int32.bswap32} reorders the bottom 32 bits (or 4 bytes),
      turning [0x1122_3344] to [0x4433_2211]. Byte swap functions exposed by
      Base use OCaml primitives to generate assembly instructions to perform
      the relevant byte swaps.

      For a more extensive list of byteswap functions, see {!Int32} and
      {!Int64}.
  *)

  (** Byte swaps bottom 16 bits (2 bytes). The values of the remaining bytes
      are undefined. *)
  external bswap16 : (int[@local_opt]) -> int = "%bswap16"
  (*_ Declared as an external so that the compiler skips the caml_apply_X wrapping even
    when compiling without cross library inlining. *)

  (**/**)

  (*_ See the Jane Street Style Guide for an explanation of [Private] submodules:

    https://opensource.janestreet.com/standards/#private-submodules *)
  module Private : sig
    (*_ For ../bench/bench_int.ml *)
    module O_F : sig
      val ( % ) : int -> int -> int
      val ( /% ) : int -> int -> int
      val ( // ) : int -> int -> float
    end
  end
end

module type Int = sig
  include Int_without_module_types (** @inline *)

  (** {2 Module types specifying integer operations.} *)

  module type Binaryable = Binaryable
  module type Hexable = Hexable
  module type Int_without_module_types = Int_without_module_types
  module type Operators = Operators
  module type Operators_unbounded = Operators_unbounded
  module type Round = Round
  module type S = S
  module type S_common = S_common
  module type S_unbounded = S_unbounded
  module type String_format = String_format
  module type To_string_format = To_string_format
end