9 %"$55.5.0+dev0-2025-04-28/%Int32$zero%int32;@@@@6../../stdlib/int32.mliee"@@%Int32@@@#one<@@@@hAAhAP@@A@@)minus_one=@@@@kooko@@B@@#neg@/>@@@4?@@@@@*%int32_negAA @@@8n9n@@7C@@#add@I@@@@@PA@@@UB@@@@@@@*%int32_addBA!@@@@YqZq@@XD@@#sub@jC@@@@qD@@@vE@@@@@@@*%int32_subBAB@@@@zt11{t1f@@yE@@#mul@F@@@@G@@@H@@@@@@@*%int32_mulBAc@@@@w||w|@@F@@#div@I@@@@J@@@K@@@@@@@*%int32_divBA@@@@zz@@G@@,unsigned_div@L@@@@M@@@N@@@@@@@@@  @  @@H@@#rem@O@@@@P@@@Q@@@@@@@*%int32_modBA@@@@F l lF l @@I@@,unsigned_rem@ R@@@@S@@@T@@@@@@@@L  L  @@J@@$succ@&U@@@+V@@@@@@*R ; ;+R ; T@@)K@@$pred@;W@@@@X@@@@@@?U  @U  @@>L@@#abs@PY@@@UZ@@@@@@TX  UX  @@SM@@'max_int c[@@@@b\ z zc\ z @@aN@@'min_int!q\@@@@p_  q_  @@oO@@&logand"@]@@@@^@@@_@@@@@@@א*%int32_andBAY@@@@ccV@@P@@%logor#@`@@@@a@@@b@@@@@@@ܐ)%int32_orBAz@@@@fttft@@Q@@&logxor$@c@@@@d@@@e@@@@@@@*%int32_xorBA@@@@ii@@R@@&lognot%@f@@@g@@@@@@l&&l&A@@S@@*shift_left&@h@@@@#inti@@@j@@@@@@@*%int32_lslBAҠ@@@@ odd od@@ T@@+shift_right'@k@@@@"l@@@'m@@@@@@@*%int32_asrBA@@@@+s,sS@@*U@@3shift_right_logical(@<n@@@@Co@@@Hp@@@@@@@*%int32_lsrBA@@@@Ly66My6y@@KV@@&of_int)@]q@@@br@@@@@-%int32_of_intAA.@@@eccfc@@dW@@&to_int*@vs@@@{t@@@@@-%int32_to_intAAG@@@~)))Y@@}X@@/unsigned_to_int+@u@@@&optionLv@@@@@@@@@aaa@@Y@@(of_float,@%floatw@@@x@@@@@3caml_int32_of_floatA@;caml_int32_of_float_unboxedA@AFF@'unboxed@@@'noalloc@@@@Z@@(to_float-@y@@@6z@@@@@3caml_int32_to_floatA@;caml_int32_to_float_unboxed0@ATm@'unboxedTYT`@@TVTa@'noallocTeTl@@Tb@@[@@)of_string.@&string{@@@|@@@@@4caml_int32_of_stringAAݠ@@@@@\@@-of_string_opt/@}@@@.~@@@ @@@ @@ @./@@-]@@)to_string0@?@@@ 9@@@@@@CKKDKj@@B^@@-bits_of_float1@@@@Y@@@@@8caml_int32_bits_of_floatA@ caml_int32_bits_of_float_unboxedA@]^";@'unboxedd"'e".@@h"$i"/@'noalloco"3p":@@s"0@@q_@@-float_of_bits2@@@@@@@@@8caml_int32_float_of_bitsA@ caml_int32_float_of_bits_unboxed@AVV@'unboxed@@@'noalloc@@@@`@@!t3A;@@@A@@@@@@@@@@@a@A@'compare4@%Int32!t@@@@%Int32!t@@@@@@ @@!@@"@@@b@@0unsigned_compare5@%Int32!t@@@#@%Int32!t@@@$@@@%@@&@@'@ @@c@@%equal6@%Int32!t@@@(@%Int32!t@@@)$bool@@@*@@+@@,@    @@d@@#min7@%Int32!t@@@-@%Int32!t@@@.%Int32!t@@@/@@0@@1@=  >  @@@"~"~"~"@@h@@@3032-bit integers.@ 0 This module provides operations on the type %int32 4 of signed 32-bit integers. Unlike the built-in #int3 type, the type %int32 ^ is guaranteed to be exactly 32-bit wide on all platforms. All arithmetic operations over %int326 are taken modulo 2"32@!.@ ' Performance notice: values of type %int32 1 occupy more memory space than values of type #int ", and arithmetic operations on %int32 $ are generally slower than those on #int'. Use %int32 ? only when the application requires exact 32-bit arithmetic.@ 9 Literals for 32-bit integers are suffixed by l: W let zero: int32 = 0l let one: int32 = 1l let m_one: int32 = -1l @@@@@@@@@@@@A6../../stdlib/int32.mli*Int32.zero35The 32-bit integer 0.@@@@@@@@@@@@@@@@)Int32.one35The 32-bit integer 1.@@@@@@@@@@@@@@@@/Int32.minus_one36The 32-bit integer -1.@@@@@@@@@@@@@@@@)Int32.neg3/Unary negation.@@@@@@@@@@@@@ @@@@)Int32.add3)Addition.@@@@@@@@@@@@@@@@@@ߠ)Int32.sub3,Subtraction.@@@@@@@@@@@@@"@%@@@@Р)Int32.mul3/Multiplication.@@@@@@@@@@@@@4@7@@@@)Int32.div3 lInteger division. This division rounds the real quotient of its arguments towards zero, as specified for *Stdlib.(/)@@!.@@@@@@@@0Division_by_zero "if the second argument is zero.@@@@@@R@U@@@@2Int32.unsigned_div3(Same as 'D@ 6, except that arguments and result are interpreted as , unsigned@1 32-bit integers.@@@@$4.08@@@@@@@@t@w@@@@Ġ)Int32.rem37Integer remainder. If !y? is not zero, the result of -Int32.rem x y & satisfies the following property: ;x = Int32.add (Int32.mul (Int32.div x y) y) (Int32.rem x y)(. If %y = 0", -Int32.rem x y( raises 0Division_by_zero!.@@@@@@@@@@@@@@@@@@٠2Int32.unsigned_rem3(Same as ?D@ 6, except that arguments and result are interpreted as , unsigned@1 32-bit integers.@@@@$4.08@@@@@@@@@@@@@ߠ*Int32.succ3,Successor. ,Int32.succ x$ is 5Int32.add x Int32.one!.@@@@@@@@@@@@@@@@@堕*Int32.pred3.Predecessor. ,Int32.pred x$ is 5Int32.sub x Int32.one!.@@@@@@@@@@@@@@@@@렕)Int32.abs3%abs x: is the absolute value of !x%. On 'min_int, this is 'min_int " itself and thus remains negative.@@@@@@@@@@@@@)@@@@-Int32.max_int3 ,The greatest representable 32-bit integer, 2"31@% - 1.@@@@@@@@@@@@@@@@-Int32.min_int3 -The smallest representable 32-bit integer, -2"31@!.@@@@@@@@@@@@ @@@@,Int32.logand34Bitwise logical and.@@@@@@@@@@@@@`@c@@@@+Int32.logor33Bitwise logical or.@@@@@@@@@@@@@r@u@@@@蠕,Int32.logxor3=Bitwise logical exclusive or.@@@@@@@@@@@@@@@@@@٠,Int32.lognot39Bitwise logical negation.@@@@@@@@@@@@@@@@@Ӡ0Int32.shift_left34Int32.shift_left x y( shifts !x0 to the left by !y ' bits. The result is unspecified if %y < 0$ or 'y >= 32!.@@@@@@@@@@@@@@@@@@ޠ1Int32.shift_right35Int32.shift_right x y( shifts !x1 to the right by !y 7 bits. This is an arithmetic shift: the sign bit of !x T is replicated and inserted in the vacated bits. The result is unspecified if %y < 0$ or 'y >= 32!.@@@@@@@@@@@@@@@@@@9Int32.shift_right_logical3=Int32.shift_right_logical x y( shifts !x1 to the right by !y h bits. This is a logical shift: zeroes are inserted in the vacated bits regardless of the sign of !x ". The result is unspecified if %y < 0$ or 'y >= 32!.@@@@@@@@@@@@@&@)@@@@,Int32.of_int3 Convert the given integer (type #int ) to a 32-bit integer (type %int32 :). On 64-bit platforms, the argument is taken modulo 2"32@!.@@@@@@@@@@@@@L@@@@ ,Int32.to_int3 'Convert the given 32-bit integer (type %int329) to an integer (type #int @). On 32-bit platforms, the 32-bit integer is taken modulo 2"31@ m, i.e. the high-order bit is lost during the conversion. On 64-bit platforms, the conversion is exact.@@@@@@@@@@@@!@o"@@@@5Int32.unsigned_to_int3(Same as ,D@ $, but interprets the argument as an (unsigned@6 integer. Returns $None > if the unsigned value of the argument cannot fit into an #int!.@@@@$4.08@@@@@@@3@4@@@@%.Int32.of_float3 Convert the given floating-point number to a 32-bit integer, discarding the fractional part (truncate towards 0). If the truncated floating-point number is outside the range [fD@", D@ Y], no exception is raised, and an unspecified, platform-dependent integer is returned.@@@@@@@@@@@@2@3@@@@$.Int32.to_float3 @@@@1/Int32.to_string3 DReturn the string representation of its argument, in signed decimal.@@@@@@@@@@@@2@I3@@@@+3Int32.bits_of_float3 Return the internal representation of the given float according to the IEEE 754 floating-point 'single format' bit layout. Bit 31 of the result represents the sign of the float; bits 30 to 23 represent the (biased) exponent; bits 22 to 0 represent the mantissa.@@@@@@@@@@@@,@X-@@@@ 3Int32.float_of_bits3 Return the floating-point number whose internal representation, according to the IEEE 754 floating-point 'single format' bit layout, is the given %int32!.@@@@@@@@@@@@@m@@@@#'Int32.t3 )An alias for the type of 32-bit integers.@@@@@@@@@@@@@@A@@@-Int32.compare3 PThe comparison function for 32-bit integers, with the same specification as .Stdlib.compare@@7. Along with the type !t0, this function 'compare7 allows the module %Int32 . to be passed as argument to the functors (Set.Make@@% and (Map.Make@@!.@@@@@@@@@@@@@@@@@@6Int32.unsigned_compare3(Same as ?D@ +, except that arguments are interpreted as (unsigned@5 32-bit integers.@@@@$4.08@@@@@@@@@@@@@+Int32.equal3>The equal function for int32s.@@@@$4.03@@@@@@@@@@@@@)Int32.min3 (Return the smaller of the two arguments.@@@@$4.13@@@@@@@@@@@@@䠕)Int32.max3 (Return the greater of the two arguments.@@@@$4.13@@@@@@@@ @@@@@Ӡ1Int32.seeded_hash3 JA seeded hash function for 32-bit ints, with the same output value as 3Hashtbl.seeded_hash@@ O. This function allows this module to be passed as argument to the functor 2Hashtbl.MakeSeeded@@!.@@@@#5.1@@@@@@@@-@0@@@@Ԡ*Int32.hash3 MAn unseeded hash function for 32-bit ints, with the same output value as ,Hashtbl.hash@@ O. This function allows this module to be passed as argument to the functor ,Hashtbl.Make@@!.@@@@#5.1@@@@@@@@M@@@@@@@@A@@@@@