module Big_int:Operations on arbitrary-precision integers.sig
..end
Big integers (type big_int
) are signed integers of arbitrary size.
type
big_int
val zero_big_int : big_int
0
.val unit_big_int : big_int
1
.val minus_big_int : big_int -> big_int
val abs_big_int : big_int -> big_int
val add_big_int : big_int -> big_int -> big_int
val succ_big_int : big_int -> big_int
val add_int_big_int : int -> big_int -> big_int
val sub_big_int : big_int -> big_int -> big_int
val pred_big_int : big_int -> big_int
val mult_big_int : big_int -> big_int -> big_int
val mult_int_big_int : int -> big_int -> big_int
val square_big_int : big_int -> big_int
val sqrt_big_int : big_int -> big_int
sqrt_big_int a
returns the integer square root of a
,
that is, the largest big integer r
such that r * r <= a
.
Raise Invalid_argument
if a
is negative.val quomod_big_int : big_int -> big_int -> big_int * big_int
(q,r) = quomod_big_int a b
, we have
a = q * b + r
and 0 <= r < |b|
.
Raise Division_by_zero
if the divisor is zero.val div_big_int : big_int -> big_int -> big_int
q
of quomod_big_int
(see above).val mod_big_int : big_int -> big_int -> big_int
r
of quomod_big_int
(see above).val gcd_big_int : big_int -> big_int -> big_int
val power_int_positive_int : int -> int -> big_int
val power_big_int_positive_int : big_int -> int -> big_int
val power_int_positive_big_int : int -> big_int -> big_int
val power_big_int_positive_big_int : big_int -> big_int -> big_int
a
raised to the power b
(the second argument). Depending
on the function, a
and b
can be either small integers
or big integers. Raise Invalid_argument
if b
is negative.val sign_big_int : big_int -> int
0
if the given big integer is zero,
1
if it is positive, and -1
if it is negative.val compare_big_int : big_int -> big_int -> int
compare_big_int a b
returns 0
if a
and b
are equal,
1
if a
is greater than b
, and -1
if a
is smaller
than b
.val eq_big_int : big_int -> big_int -> bool
val le_big_int : big_int -> big_int -> bool
val ge_big_int : big_int -> big_int -> bool
val lt_big_int : big_int -> big_int -> bool
val gt_big_int : big_int -> big_int -> bool
val max_big_int : big_int -> big_int -> big_int
val min_big_int : big_int -> big_int -> big_int
val num_digits_big_int : big_int -> int
val string_of_big_int : big_int -> string
val big_int_of_string : string -> big_int
-
or +
sign,
followed by one or several decimal digits.val big_int_of_int : int -> big_int
val is_int_big_int : big_int -> bool
int
)
without loss of precision. On a 32-bit platform,
is_int_big_int a
returns true
if and only if
a
is between 230 and 230-1. On a 64-bit platform,
is_int_big_int a
returns true
if and only if
a
is between -262 and 262-1.val int_of_big_int : big_int -> int
int
).
Raises Failure "int_of_big_int"
if the big integer
is not representable as a small integer.val big_int_of_int32 : int32 -> big_int
val big_int_of_nativeint : nativeint -> big_int
val big_int_of_int64 : int64 -> big_int
val int32_of_big_int : big_int -> int32
Failure
if the big integer is outside the
range [-2{^31}, 2{^31}-1]
.val nativeint_of_big_int : big_int -> nativeint
Failure
if the big integer is outside the
range [Nativeint.min_int, Nativeint.max_int]
.val int64_of_big_int : big_int -> int64
Failure
if the big integer is outside the
range [-2{^63}, 2{^63}-1]
.val float_of_big_int : big_int -> float
val and_big_int : big_int -> big_int -> big_int
val or_big_int : big_int -> big_int -> big_int
val xor_big_int : big_int -> big_int -> big_int
val shift_left_big_int : big_int -> int -> big_int
shift_left_big_int b n
returns b
shifted left by n
bits.
Equivalent to multiplication by 2^n
.val shift_right_big_int : big_int -> int -> big_int
shift_right_big_int b n
returns b
shifted right by n
bits.
Equivalent to division by 2^n
with the result being
rounded towards minus infinity.val shift_right_towards_zero_big_int : big_int -> int -> big_int
shift_right_towards_zero_big_int b n
returns b
shifted
right by n
bits. The shift is performed on the absolute
value of b
, and the result has the same sign as b
.
Equivalent to division by 2^n
with the result being
rounded towards zero.val extract_big_int : big_int -> int -> int -> big_int
extract_big_int bi ofs n
returns a nonnegative number
corresponding to bits ofs
to ofs + n - 1
of the
binary representation of bi
. If bi
is negative,
a two's complement representation is used.