Caml1999I037*1Stdlib__Nativeint$zero<)nativeintM@@@g@-nativeint.mlihh@@@@@#one=@@@h@kk@@A@@)minus_one>@@@i@n  n %@@+B@@#neg?@,@@@j0@@@k@@l.%nativeint_negAA @@@3qDD4qD|@@CC@@#add@@D@@@m@J@@@nN@@@o@@p@@q.%nativeint_addBA@@@@QtRt@@aD@@#subA@b@@@r@h@@@sl@@@t@@u@@v.%nativeint_subBA<@@@@owpw 2@@E@@#mulB@@@@w@@@@x@@@y@@z@@{.%nativeint_mulBAZ@@@@z H Hz H @@F@@#divC@@@@|@@@@}@@@~@@@@.%nativeint_divBAx@@@@}  }  @@G@@,unsigned_divD@@@@@@@@@@@@@@@@D  D  @@H@@#remE@@@@@@@@@@@@@@@.%nativeint_modBA@@@@J d dJ d @@I@@,unsigned_remF@@@@@@@@@@@@@@@@R  R  >@@ J@@$succG@ @@@@@@@@@X  X  @@K@@$predH@@@@#@@@@@@!\--"\-N@@1L@@#absI@2@@@6@@@@@@4`5`@@DM@@$sizeJ#intA@@@@Cd11Dd1?@@SN@@'max_intKR@@@@PhQh@@`O@@'min_intL_@@@@]m\\^m\s@@mP@@&logandM@n@@@@t@@@x@@@@@@@.%nativeint_andBAH@@@@{r|r;@@Q@@%logorN@@@@@@@@@@@@@@@-%nativeint_orBAf@@@@uYYuY@@R@@&logxorO@@@@@@@@@@@@@@@.%nativeint_xorBA@@@@xx@@S@@&lognotP@@@@@@@@@@{++{+N@@T@@*shift_leftQ@@@@@@@@@@@@@@@.%nativeint_lslBA@@@@~qq~q@@U@@+shift_rightR@@@@@@@@@@@@@@@.%nativeint_asrBAӠ@@@@@@V@@3shift_right_logicalS@@@@@@@@!@@@@@@@.%nativeint_lsrBA@@@@$%@@4W@@&of_intT@@@@9@@@@@1%nativeint_of_intAA @@@;<?@@KX@@&to_intU@L@@@ @@@@@1%nativeint_to_intAA @@@RS@@bY@@/unsigned_to_intV@c@@@&optionL*@@@@@@@@@lddmd@@|Z@@(of_floatW@%floatD@@@@@@@@ɐ7caml_nativeint_of_floatA@?caml_nativeint_of_float_unboxedA@@MM@'unboxed@@@'noalloc@@@@[@@(to_floatX@@@@4@@@@@̐7caml_nativeint_to_floatA@?caml_nativeint_to_float_unboxed.@A{@'unboxed{{@@{}{@'noalloc{{@@{@@\@@(of_int32Y@%int32N@@@@@@@@ϐ3%nativeint_of_int32AA@@@@@]@@(to_int32Z@@@@@@@@@Ґ3%nativeint_to_int32AAǠ@@@iii@@ ^@@)of_string[@&stringQ@@@@@@@@Ր8caml_nativeint_of_stringAA@@@@@"_@@-of_string_opt\@@@@+@@@@@@@@@*rr+r@@:`@@)to_string]@;@@@5@@@@@@=> @@Ma@@!t^;@@@AN@@@@@@@L ] ]M ] o@@@@\b@A@'compare_@@@@@@@@#@@@@@@@@d  e  @@tc@@0unsigned_compare`@@@@@@@@:@@@@@@@@{!!|!!@@d@@%equala@/@@@@4@@@$boolE@@@@@@@@"b"b"b"{@@e@@#minb@H@@@@M@@@P@@@@@@@@""""@@f@@#maxc@^@@@@c@@@f@@@@@@@@####"@@g@@+seeded_hashd@@@@@z@@@@@@@@@@@#e#e#e#@@h@@$hashe@@@@@@@@@@$e$e$e$x@@i@@@o;/1Stdlib__Nativeint0Q:38Yh$ce𬠠&Stdlib0Lku]8_٠8CamlinternalFormatBasics0%FU(Q/Tu@@@Caml1999T037NG7C1Stdlib__Nativeint*ocaml.text&_none_@@A k 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 pointer 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. Performance notice: values of type [nativeint] occupy more memory space than values of type [int], and arithmetic operations on [nativeint] are generally slower than those on [int]. Use [nativeint] only when the application requires the extra bit of precision over the [int] type. Literals for native integers are suffixed by n: {[ let zero: nativeint = 0n let one: nativeint = 1n let m_one: nativeint = -1n ]} -nativeint.mliP77f@@@@@@3@@@@@@#intA;@@@A@@@@@:@A@$charB;@@A@@@@@>@A@&stringQ;@@ A@@@@@B@@@%bytesC;@@ A@@@@@F@@@%floatD;@@A@@@@@J@@@$boolE;@@%falsec@@T@$trued@@Z@@@A@@@@@[@A@$unitF;@@"()e@@e@@@A@@@@@f@A@ #exnG;@@@A@@@@@j@@@#effH;@@O@A@A@@@@@@s@@@,continuationI;@@Q@@P@B@A@nY@@@@@@@@@%arrayJ;@@R@A@A@@@@@@@@@ $listK;@@S@A"[]f@@@"::g@@@T@@@ @@A@Y@@@@@@@@&optionL;@@V@A$Noneh@@@$Somei@@@@@A@Y@@@@@@@@)nativeintM;@@A@@@@@@@@%int32N;@@A@@@@@@@@%int64O;@@A@@@@@@@@&lazy_tP;@@X@AJA@Y@@@@@@@@5extension_constructorR;@@A@@@@@@@@*floatarrayS;@@A@@@@@@@@&iarrayT;@@Y@A[A@Y@@@@@@@@*atomic_locU;@@Z@AdA@@@@@@@@@.Assert_failure`#@@@@@J@@@@@@@@[@@A=ocaml.warn_on_literal_pattern @ @0Division_by_zero]#@@@A  @+End_of_file\#$@@@A@'FailureY#,@'@@A!$$@0Invalid_argumentX#5@0@@A*$-#-@-Match_failureV#>@@=@9@;@@a@@A;5>4>@)Not_foundZ#O@@@AC=F<F@-Out_of_memoryW#W@@@AKENDN@.Stack_overflow^#_@@@ASMVLV@.Sys_blocked_io_#g@@@A[U^T^@)Sys_error[#o@j@@Ad^g]g@:Undefined_recursive_modulea#x@@w@s@u@@h@@Auoxnx@:Continuation_already_takenb#@@@A}wv@&Stdlib@Ax$zerohh@гР)nativeinthh@@ @@@@@@h@)ocaml.doc6 The native integer 0.ii@@@@@@@@@@@@@@@@@#onekk@г)nativeintkk@@ @@@3@K8@A@@@k @96 The native integer 1.ll @@@@@@@A@@@Iꐠ@@@@@@!)minus_onen n @г>)nativeintn n %@@ @@@3@8K6@A@@@n   @p7 The native integer -1. o&&o&B@@@@@@@&B@@@!@@@@@@!#neg$qDM%qDP@б@гw)nativeint/qDS0qD\@@ @@@310011111@:M8@A@@г)nativeint>qD`?qDi@@ @@@@@@@@@@.%nativeint_negAA @@@NqDDOqD|@1 Unary negation. \r}}]r}@@@@@@@uC@@@q@@@@@@8#addttut@б@гǠ)nativeinttt@@ @@@3@Qf?@A@@б@гؠ)nativeinttt@@ @@@@@г堐)nativeinttt@@ @@@@@@@@!@@@'@@$* @@.%nativeint_addBAb@@@@tt@!+ Addition. uu@@@@@@@D@@@2Ӑ@@@@@@J#subww@б@г))nativeintww @@ @@@3@cx?@A@@б@г:)nativeintw w @@ @@@@@гG)nativeintw w @@ @@@@@@@@!@@@'@@$* @@.%nativeint_subBAĠ@@@@ww 2@. Subtraction.  x 3 3!x 3 F@@@@@@@9E@@@5@@@@@@J#mul8z H Q9z H T@б@г)nativeintCz H WDz H `@@ @@@3EDDEEEEE@cx?@A@@б@г)nativeintTz H dUz H m@@ @@@@@г)nativeintaz H qbz H z@@ @@@@@@@@!@@@'@@$* @@.%nativeint_mulBA&@@@@tz H Huz H @吠1 Multiplication. {  {  @@@@@@@F@@@@@@@@@J#div}  }  @б@г)nativeint}  }  @@ @@@3@cx?@A@@б@г)nativeint}  }  @@ @@@@@г )nativeint}  }  @@ @@@@@@@@!@@@'@@$* @@.%nativeint_divBA@@@@}  }  @G Integer division. This division rounds the real quotient of its arguments towards zero, as specified for {!Stdlib.(/)}. @raise Division_by_zero if the second argument is zero. ~  B  @@@@@@@G@@@X@@@@@@J,unsigned_divD  D  @б@гO)nativeintD  D  @@ @@@3      @cx?@A@@б@г`)nativeintD  D  @@ @@@@@гm)nativeint%D  &D  @@ @@@@@@@@!@@@'@@$* @@@3D  @ x Same as {!div}, except that arguments and result are interpreted as {e unsigned} native integers. @since 4.08 @E  AH P b@@@@@@@YH@@@T@@@@@@C#remWJ d mXJ d p@б@г)nativeintbJ d scJ d |@@ @@@3dccddddd@\q8@A@@б@г)nativeintsJ d tJ d @@ @@@@@гȠ)nativeintJ d J d @@ @@@@@@@@!@@@'@@$* @@.%nativeint_modBAE@@@@J d dJ d @ W Integer remainder. If [y] is not zero, the result of [Nativeint.rem x y] satisfies the following properties: [Nativeint.zero <= Nativeint.rem x y < Nativeint.abs 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]. K  P  @@@@@@@I@@@@@@@@@J,unsigned_remR  R  @б@г )nativeintR  R  $@@ @@@3@cx?@A@@б@г)nativeintR  (R  1@@ @@@@@г*)nativeintR  5R  >@@ @@@@@@@@!@@@'@@$* @@@R  @` x Same as {!rem}, except that arguments and result are interpreted as {e unsigned} native integers. @since 4.08 S ? ?V  @@@@@@@J@@@p@@@@@@C$succX  X  @б@гg)nativeintX   X  @@ @@@3!  !!!!!@\q8@A@@гv)nativeint.X  /X  @@ @@@@@@@@@@@9X   @ F Successor. [Nativeint.succ x] is [Nativeint.add x Nativeint.one]. FY  GZ +@@@@@@@_K@@@Z@@@@@@1$pred]\-1^\-5@б@г)nativeinth\-8i\-A@@ @@@3jiijjjjj@J_8@A@@г)nativeintw\-Ex\-N@@ @@@@@@@@@@@\-- @򐠠 H Predecessor. [Nativeint.pred x] is [Nativeint.sub x Nativeint.one]. ]OO^`@@@@@@@L@@@@@@@@@1#abs``@б@г)nativeint``@@ @@@3@J_8@A@@г)nativeint``@@ @@@@@@@@@@@` @; k [abs x] is the absolute value of [x]. On [min_int] this is [min_int] itself and thus remains negative. ab/@@@@@@@M@@@K쐠@@@@@@1$size d15d19@гˠ#intd1<d1?@@ @@@3@H]6@A@@@d11 @r x The size in bits of a native integer. This is equal to [32] on a 32-bit platform and to [64] on a 64-bit platform. e@@f@@@@@@@(N@@@#@@@@@@!'max_int!&h'h@гw)nativeint/h0h@@ @@@310011111@8K6@A@@@9h @ ~ The greatest representable native integer, either 2{^31} - 1 on a 32-bit platform, or 2{^63} - 1 on a 64-bit platform. FiGk1Z@@@@@@@_O@@@Z@@@@@@!'min_int"]m\`^m\g@г)nativeintfm\jgm\s@@ @@@3hgghhhhh@8K6@A@@@pm\\ @ x The smallest representable native integer, either -2{^31} on a 32-bit platform, or -2{^63} on a 64-bit platform. }ntt~p@@@@@@@P@@@@@@@@@!&logand#rr@б@г砐)nativeintrr@@ @@@3@:M8@A@@б@г)nativeintrr@@ @@@@@г)nativeintrr(@@ @@@@@@@@!@@@'@@$* @@.%nativeint_andBA@@@@rr;@A6 Bitwise logical and. s<<s<W@@@@@@@Q@@@R󐠠@@@@@@J%logor$uYbuYg@б@гI)nativeintuYjuYs@@ @@@3@cx?@A@@б@гZ)nativeintuYwuY@@ @@@@@гg)nativeintuY uY@@ @@@@@@@@!@@@'@@$* @@-%nativeint_orBA@@@@2uYY3uY@5 Bitwise logical or. @vAv@@@@@@@YR@@@U@@@@@@J&logxor%XxYx@б@г)nativeintcxdx@@ @@@3eddeeeee@cx?@A@@б@г)nativeinttxux@@ @@@@@гɠ)nativeintxx@@ @@@@@@@@!@@@'@@$* @@.%nativeint_xorBAF@@@@xx@? Bitwise logical exclusive or. yy)@@@@@@@S@@@@@@@@@J&lognot&{+/{+5@б@г )nativeint{+8{+A@@ @@@3@cx?@A@@г)nativeint{+E{+N@@ @@@@@@@@@@@{++ @O; Bitwise logical negation. |OO|Oo@@@@@@@T@@@_@@@@@@1*shift_left'~qz~q@б@гV)nativeint~q~q@@ @@@3@J_8@A@@б@г#int~q ~q@@ @@@@@гt)nativeint,~q-~q@@ @@@@@@@@!@@@'@@$* @@.%nativeint_lslBA@@@@?~qq@~q@ [Nativeint.shift_left x y] shifts [x] to the left by [y] bits. The result is unspecified if [y < 0] or [y >= bitsize], where [bitsize] is [32] on a 32-bit platform and [64] on a 64-bit platform. MNj@@@@@@@fU@@@b@@@@@@J+shift_right(ef@б@г)nativeintpq@@ @@@3rqqrrrrr@cx?@A@@б@гT#int@@ @@@@@г֠)nativeint@@ @@@@@@@@!@@@'@@$* @@.%nativeint_asrBAS@@@@@ [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. The result is unspecified if [y < 0] or [y >= bitsize]. @@@@@@@V@@@#Đ@@@@@@J3shift_right_logical)@б@г)nativeint@@ @@@3@cx?@A@@б@г#int@@ @@@@@г8)nativeint@@ @@@@@@@@!@@@'@@$* @@.%nativeint_lsrBA@@@@  @t [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]. The result is unspecified if [y < 0] or [y >= bitsize].   @@@@@@@ *W@@@ &@@@@@@J&of_int* ) *@б@г #int 4 5@@ @@@3 6 5 5 6 6 6 6 6@cx?@A@@г)nativeint C  D)@@ @@@@@@@@@@1%nativeint_of_intAA@@@ R S?@Ð S Convert the given integer (type [int]) to a native integer (type [nativeint]).  `@@ a@@@@@@@ yX@@@ u@@@@@@7&to_int+ x y@б@гˠ)nativeint  @@ @@@3        @Pe>@A@@г e#int  @@ @@@@@@@@@@1%nativeint_to_intAAT@@@  @ Convert the given native integer (type [nativeint]) to an integer (type [int]). The high-order bit is lost during the conversion.   Mb@@@@@@@ Y@@@# Đ@@@@@@7/unsigned_to_int, dh dw@б@г )nativeint dz d@@ @@@3        @Pe>@A@@г @&option d d@г #int d d@@ @@@@@@@@@ @@@$@@!'@@@ dd@k Same as {!to_int}, but interprets the argument as an {e unsigned} integer. Returns [None] if the unsigned value of the argument cannot fit into an [int]. @since 4.08   9K@@@@@@@ !Z@@*@{ @@@@@@@(of_float- MV M^@б@г 점%float *Ma +Mf@@ @@@3 , + + , , , , ,@Yn8@A@@г )nativeint 9Mj :Ms@@ @@@@@@@@@@7caml_nativeint_of_floatA@?caml_nativeint_of_float_unboxedA@@ JMM K@'unboxed Q R@@ U V@'noalloc \ ]@@ `@А ? Convert the given floating-point number to a native integer, discarding the fractional part (truncate towards 0). If the truncated floating-point number is outside the range \[{!Nativeint.min_int}, {!Nativeint.max_int}\], no exception is raised, and an unspecified, platform-dependent integer is returned.  m n@@@@@@@ [@,,@)(@'&@# @ @@@@@@W=(to_float.  %@б@г ᠐)nativeint ( 1@@ @@@3        @p^@A@@г j%float 5 :@@ @@@@@@@@@@7caml_nativeint_to_floatA@?caml_nativeint_to_float_unboxedo@A  {@'unboxed { {@@ {} {@'noalloc { {@@ {@ > > Convert the given native integer to a floating-point number.   @@@@@@@ \@++@)(@'&@# @ X @@@@@@V=(of_int32/  @б@г K%int32  @@ @@@3        @o]@A@@г ^)nativeint  @@ @@@@@@@@@@3%nativeint_of_int32AAؠ@@@ % &@ I Convert the given 32-bit integer (type [int32]) to a native integer.  3 4Mg@@@@@@@ L]@@@  H@@@@@@7(to_int320 Kir Liz@б@г )nativeint Vi} Wi@@ @@@ 3 X W W X X X X X@Pe>@A@@г %int32 ei fi@@ @@@ @@@@@ @@3%nativeint_to_int32AA '@@@ tii ui@ 吠 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.   w@@@@@@@ ^@@@  @@@@@@7)of_string1  @б@г o&string  @@ @@@ 3        @Pe>@A@@г )nativeint  @@ @@@ @@@@@@@8caml_nativeint_of_stringAA v@@@  @ 4  Convert the given string to a native integer. The string is read in decimal (by default, or if the string begins with [0u]) or in hexadecimal, octal or binary if the string begins with [0x], [0o] or [0b] respectively. The [0u] prefix reads the input as an unsigned integer in the range [[0, 2*Nativeint.max_int+1]]. If the input exceeds {!Nativeint.max_int} it is converted to the signed integer [Int64.min_int + input - Nativeint.max_int - 1]. @raise Failure if the given string is not a valid representation of an integer, or if the integer represented exceeds the range of integers representable in type [nativeint].   *p@@@@@@@ _@@@ E 搠@@@@@@7-of_string_opt2 rv r@б@г &string r r@@ @@@3        @Pe>@A@@г b&option r r@г U)nativeint r r@@ @@@@@@@@@ @@@$@@!'@@@ rr@ L Same as [of_string], but return [None] instead of raising. @since 4.05  * +@@@@@@@ C`@@*@  >@@@@@@@)to_string3 A B @б@г )nativeint L  M @@ @@@3 N M M N N N N N@Yn8@A@@г %&string [  \ @@ @@@@@@@@@@@ f @ ֐ ? Return the string representation of its argument, in decimal.  s   t  [@@@@@@@ a@@@  @@@@@@1A+!t4A  ] b  ] c@@;@@@A @@@@@@@  ] ]  ] o@  + An alias for the type of native integers.   p p  p @@@@@@@@@ b@@@Aг)nativeint  ] f@@3        @_tM*;@@@A2@@@@@@@@&#@@@A%@@' * ː%$@$$@@@$@$@@3        @@A32@'compare5      @б@гP!t      @@ @@@3        @2[U@A@@б@гa!t      @@ @@@ @@г ̠#int      @@ @@@!@@@@@"!@@@'@@#$* @@@   @ w  The comparison function for native integers, with the same specification as {!Stdlib.compare}. Along with the type [t], this function [compare] allows the module [Nativeint] to be passed as argument to the functors {!Set.Make} and {!Map.Make}.     !!@@@@@@@ -c@@@  (@@@@@@C0unsigned_compare6 +!! ,!!@б@г!t 6!! 7!!@@ @@@$3 8 7 7 8 8 8 8 8@\q8@A@@б@г!t G!! H!!@@ @@@%@@г '#int T!! U!!@@ @@@&@@@@@'!@@@'@@($* @@@ b!!@ Ґ q Same as {!compare}, except that arguments are interpreted as {e unsigned} native integers. @since 4.08  o!! p"N"`@@@@@@@ d@@@  @@@@@@C%equal7 "b"f "b"k@б@г!t "b"m "b"n@@ @@@)3        @\q8@A@@б@г!t "b"r "b"s@@ @@@*@@г m$bool "b"w "b"{@@ @@@+@@@@@,!@@@'@@-$* @@@ "b"b@ - 5 The equal function for native ints. @since 4.03  "|"| ""@@@@@@@ e@@@ = ސ@@@@@@C#min8 "" ""@б@гa!t "" ""@@ @@@.3        @\q8@A@@б@гr!t "" ""@@ @@@/@@г!t "" ""@@ @@@0@@@@@1!@@@'@@2$* @@@""@ : Return the smaller of the two arguments. @since 4.13 %""&# # @@@@@@@>f@@@ 9@@@@@@C#max9<##=##@б@г!tG##H##@@ @@@33IHHIIIII@\q8@A@@б@г͠!tX##Y##@@ @@@4@@гڠ!te##!f##"@@ @@@5@@@@@6!@@@'@@7$* @@@s##@ 㐠 ; Return the greater of the two arguments. @since 4.13 #####`#c@@@@@@@g@@@ @@@@@@C+seeded_hash:#e#i#e#t@б@гu#int#e#w#e#z@@ @@@83@\q8@A@@б@г(!t#e#~#e#@@ @@@9@@г#int#e##e#@@ @@@:@@@@@;!@@@'@@<$* @@@#e#e@ > A seeded hash function for native ints, with the same output value as {!Hashtbl.seeded_hash}. This function allows this module to be passed as argument to the functor {!Hashtbl.MakeSeeded}. @since 5.1 ##$R$c@@@@@@@h@@@ N@@@@@@C$hash;$e$i$e$m@б@гr!t$e$p$e$q@@ @@@=3@\q8@A@@гߠ#int $e$u $e$x@@ @@@>@@@@@?@@@$e$e @ An unseeded hash function for native ints, with the same output value as {!Hashtbl.hash}. This function allows this module to be passed as argument to the functor {!Hashtbl.Make}. @since 5.1 $$y$y%%:%K@@@@@@@=i@@@ 8@@@@@@1@  @  p@ P ;@  @  @ m 4@  @  t@ M @  @  [@ ; @  @  @ f Q@ 1 @@@g.@@@`'@@g@@@@p@P)@@wP@*@@Z@:@A@v@V@@k@K@@r@@3@t@A@ H************************************************************************A@@A@L@ H BMMBM@ H OCaml CC@ H DD3@ H Xavier Leroy, projet Cristal, INRIA Rocquencourt E44E4@ H FF@ H Copyright 1996 Institut National de Recherche en Informatique et GG@ H en Automatique. HHg@ H IhhIh@ H All rights reserved. This file is distributed under the terms of JJ@ H the GNU Lesser General Public License version 2.1, with the KKN@ H special exception on linking described in the file LICENSE. LOOLO@ H MM@ H************************************************************************NN5@ l* 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 pointer 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. Performance notice: values of type [nativeint] occupy more memory space than values of type [int], and arithmetic operations on [nativeint] are generally slower than those on [int]. Use [nativeint] only when the application requires the extra bit of precision over the [int] type. Literals for native integers are suffixed by n: {[ let zero: nativeint = 0n let one: nativeint = 1n let m_one: nativeint = -1n ]} ᠠ7* The native integer 0.E7* The native integer 1.8* The native integer -1. ݠ2* Unary negation.  ,* Addition.  2/* Subtraction.  Ӡ2* Multiplication.  t * Integer division. This division rounds the real quotient of its arguments towards zero, as specified for {!Stdlib.(/)}. @raise Division_by_zero if the second argument is zero.   y* Same as {!div}, except that arguments and result are interpreted as {e unsigned} native integers. @since 4.08  X* Integer remainder. If [y] is not zero, the result of [Nativeint.rem x y] satisfies the following properties: [Nativeint.zero <= Nativeint.rem x y < Nativeint.abs 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].  ^ y* Same as {!rem}, except that arguments and result are interpreted as {e unsigned} native integers. @since 4.08   G* Successor. [Nativeint.succ x] is [Nativeint.add x Nativeint.one].  I* Predecessor. [Nativeint.pred x] is [Nativeint.sub x Nativeint.one].  y l* [abs x] is the absolute value of [x]. On [min_int] this is [min_int] itself and thus remains negative.  3 y* The size in bits of a native integer. This is equal to [32] on a 32-bit platform and to [64] on a 64-bit platform.  * The greatest representable native integer, either 2{^31} - 1 on a 32-bit platform, or 2{^63} - 1 on a 64-bit platform.  ˠ y* The smallest representable native integer, either -2{^31} on a 32-bit platform, or -2{^63} on a 64-bit platform.  7* Bitwise logical and.  96* Bitwise logical or. ڠ * Bitwise logical exclusive or. {<* Bitwise logical negation. 4 * [Nativeint.shift_left x y] shifts [x] to the left by [y] bits. The result is unspecified if [y < 0] or [y >= bitsize], where [bitsize] is [32] on a 32-bit platform and [64] on a 64-bit platform. ֠ * [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. The result is unspecified if [y < 0] or [y >= bitsize]. w * [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]. The result is unspecified if [y < 0] or [y >= bitsize].  T* Convert the given integer (type [int]) to a native integer (type [nativeint]). ̠ * Convert the given native integer (type [nativeint]) to an integer (type [int]). The high-order bit is lost during the conversion.  * Same as {!to_int}, but interprets the argument as an {e unsigned} integer. Returns [None] if the unsigned value of the argument cannot fit into an [int]. @since 4.08 * @* Convert the given floating-point number to a native integer, discarding the fractional part (truncate towards 0). If the truncated floating-point number is outside the range \[{!Nativeint.min_int}, {!Nativeint.max_int}\], no exception is raised, and an unspecified, platform-dependent integer is returned. Ƞ ?* Convert the given native integer to a floating-point number. ] J* Convert the given 32-bit integer (type [int32]) to a native integer.  * 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.  * Convert the given string to a native integer. The string is read in decimal (by default, or if the string begins with [0u]) or in hexadecimal, octal or binary if the string begins with [0x], [0o] or [0b] respectively. The [0u] prefix reads the input as an unsigned integer in the range [[0, 2*Nativeint.max_int+1]]. If the input exceeds {!Nativeint.max_int} it is converted to the signed integer [Int64.min_int + input - Nativeint.max_int - 1]. @raise Failure if the given string is not a valid representation of an integer, or if the integer represented exceeds the range of integers representable in type [nativeint]. p M* Same as [of_string], but return [None] instead of raising. @since 4.05  @* Return the string representation of its argument, in decimal. Ԡ ,* An alias for the type of native integers.  * The comparison function for native integers, with the same specification as {!Stdlib.compare}. Along with the type [t], this function [compare] allows the module [Nativeint] to be passed as argument to the functors {!Set.Make} and {!Map.Make}. 9 r* Same as {!compare}, except that arguments are interpreted as {e unsigned} native integers. @since 4.08 ᠠ 6* The equal function for native ints. @since 4.03  ;* Return the smaller of the two arguments. @since 4.13 1 <* Return the greater of the two arguments. @since 4.13 ٠ * A seeded hash function for native ints, with the same output value as {!Hashtbl.seeded_hash}. This function allows this module to be passed as argument to the functor {!Hashtbl.MakeSeeded}. @since 5.1  * An unseeded hash function for native ints, with the same output value as {!Hashtbl.hash}. This function allows this module to be passed as argument to the functor {!Hashtbl.Make}. @since 5.1 ;@?)../ocamlc0-strict-sequence(-absname"-w5+a-4-9-41-42-44-45-48"-g+-warn-error"+A*-bin-annot)-nostdlib*-principal"-o5stdlib__Nativeint.cmi"-clm D/builds/workspace/precheck/flambda/false/label/ocaml-linux-32/stdlib @@0!!CLCҒ3qppqqqqq@o@@8CamlinternalFormatBasics0%FU(Q/Tu&Stdlib0Lku]8_٠0Q:38Yh$ce@0Q:38Yh$ceAjS@tې@b!w  @Y4s@b@)uƐ'@  p@@@@ǐڐ&@@@@J@@  X@@@  ]@Đ l @ ܐ @  @k@ / i  @ذ2@#Ck  `@@  @@N@    H Y   F@@P@@