Caml1999I037 O$-Stdlib__Uchar!t/;@@@A@@@@@)uchar.mliTddUkx@)immediateUkn Ukw@@ Ukk @@A@@@A@#min0@@@@]pp]p{@@#A@@#max1 @@@@$`%`@@/B@@#bom2@@@@0c1c@@;C@@#rep3%@@@@@@@@@@J x xJ x @@J@@'is_char:@@@@J@@@@@@M  M  @@K@@'of_char;@$charB@@@@@@@@@P  P  4@@L@@'to_char<@@@@@@@@@@S h hS h @@M@@.unsafe_to_char=@@@@)@@@@@@Y  Y  @@N@@%equal>@@@@@@@@@@@@@@@@ \ * * \ * D@@O@@'compare?@@@@@@@@@@@@@@@@#_ g g$_ g @@.P@@+seeded_hash@@@@@@ @@@@@@@@@@@;b  <b  @@FQ@@$hashA@2@@@@@@@@@Mi  Ni  @@XR@@*utf_decodeB;@@@A@@@@@Wu==Xu=Z@)immediate^u=P_u=Y@@bu=M @@A@lS@A@3utf_decode_is_validC@@@@@@@@@@tyuy@@T@@0utf_decode_ucharD@@@@n@@@@@@}jj}j@@U@@1utf_decode_lengthE@$@@@*@@@@@@D@@V@@*utf_decodeF@9@@@@@@@?@@@@@@@@@@W@@2utf_decode_invalidG@P@@@Q@@@@@@@@X@@;utf_8_decode_length_of_byteH@@@@f@@@@@@@@Y@@7max_utf_8_decode_lengthIs@@@@ @@Z@@1utf_8_byte_lengthJ@@@@@@@@@@@@[@@2utf_16_byte_lengthK@@@@@@@@@@   -@@\@@@k:.-Stdlib__Uchar056uf4[_&Stdlib0Lku]8_٠8CamlinternalFormatBasics0%FU(Q/Tu@@@Caml1999T037W 3.XC-Stdlib__Uchar*ocaml.text&_none_@@A & Unicode characters. @since 4.03 )uchar.mliP77RPb@@@@@@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@AxA+!tATdiTdj@@;@@@A@@@@@TddUkx@)immediateUknUkw@@Ukk @)ocaml.doc The type for Unicode characters. A value of this type represents a Unicode {{:http://unicode.org/glossary/#unicode_scalar_value}scalar value} which is an integer in the ranges [0x0000]...[0xD7FF] or [0xE000]...[0x10FFFF]. Vyy[Qn@@@@@@@A@@@@@A@@@@@@@@@-,@#min]pt]pw@гC!t]pz]p{@@ @@@3@NH@A@@@]pp @=2 [min] is U+0000. ^||^|@@@@@@@A@@@M@@@@@@!#max``@гz!t``@@ @@@3@8K6@A@@@` @t4 [max] is U+10FFFF. aa@@@@@@@*B@@@%@@@@@@!#bom(c)c@г!t1c2c@@ @@@332233333@8K6@A@@@;c @ [bom] is U+FEFF, the {{:http://unicode.org/glossary/#byte_order_mark}byte order mark} (BOM) character. @since 4.06 HdIh<N@@@@@@@aC@@@\@@@@@@!#rep_jPT`jPW@г蠐!thjPZijP[@@ @@@3jiijjjjj@8K6@A@@@rjPP @␠ } [rep] is U+FFFD, the {{:http://unicode.org/glossary/#replacement_character}replacement} character. @since 4.06 k\\o@@@@@@@D@@@@@@@@@!$succqq@б@г!!tqq@@ @@@3@:M8@A@@г0!tqq@@ @@@@@@@@@@@q @+ [succ u] is the scalar value after [u] in the set of Unicode scalar values. @raise Invalid_argument if [u] is {!max}. ruGw@@@@@@@E@@@;ܐ@@@@@@1$predwy}wy@б@гj!twywy@@ @@@3@J_8@A@@гy!twywy@@ @@@@@@@@@@@wyy @t [pred u] is the scalar value before [u] in the set of Unicode scalar values. @raise Invalid_argument if [u] is {!min}. x{@@@@@@@*F@@@%@@@@@@1(is_valid(})}@б@г#int3}"4}%@@ @@@354455555@J_8@A@@г$boolB})C}-@@ @@@@@@@@@@@M} @ [is_valid n] is [true] if and only if [n] is a Unicode scalar value (i.e. in the ranges [0x0000]...[0xD7FF] or [0xE000]...[0x10FFFF]).Z~..[v@@@@@@@sG@@@n@@@@@@1&of_intqArA@б@гO#int|A}A@@ @@@3~}}~~~~~@J_8@A@@г !tAA@@ @@@@@@@@@@@A @ m [of_int i] is [i] as a Unicode character. @raise Invalid_argument if [i] does not satisfy {!is_valid}. BD  H@@@@@@@H@@@@@@@@@1Đ"/*F J JF J Q@@@@@@3@CX1@A-unsafe_of_intG R VG R c@б@г#intG R fG R i@@ @@@@@гe!tG R mG R n@@ @@@'@@@@@*@@@G R R @@I@@ @@0"/*H o oH o v@@@@@@3@B=@A&to_intJ x |J x @б@г!tJ x J x @@ @@@@@г#int&J x 'J x @@ @@@'@@@@@*@@@1J x x @ " [to_int u] is [u] as an integer. >K  ?K  @@@@@@@WJ@@@R@@@@@@I'is_charUM  VM  @б@гࠐ!t`M  aM  @@ @@@3baabbbbb@b]8@A@@г-$booloM  pM  @@ @@@@@@@@@@@zM   @ꐠ G [is_char u] is [true] if and only if [u] is a latin1 OCaml character. N  N  @@@@@@@K@@@@@@@@@1'of_charP  !P  (@б@гw$charP  +P  /@@ @@@3@J_8@A@@г8!tP  3P  4@@ @@@@@@@@@@@P   @3 , [of_char c] is [c] as a Unicode character. Q 5 5Q 5 f@@@@@@@L@@@C䐠@@@@@@1'to_charS h lS h s@б@гr!tS h vS h w@@ @@@3@J_8@A@@гϠ$charS h {S h @@ @@@@@@@@@@@ S h h @| s [to_char u] is [u] as an OCaml latin1 character. @raise Invalid_argument if [u] does not satisfy {!is_char}. T  V  @@@@@@@2M@@@-@@@@@@1;:"/*7X  8X  @@@@@@365566666@CX1@A.unsafe_to_char CY  DY  @б@гΠ!tNY  OY  @@ @@@@@г)$char[Y  \Y  @@ @@@'@@@@@*@@@fY   @@~N@@ @@0|{"/*xZ ! !yZ ! (@@@@@@3wvvwwwww@B=@A%equal!\ * .\ * 3@б@г!t\ * 6\ * 7@@ @@@@@б@г!t\ * ;\ * <@@ @@@)@@гi$bool\ * @\ * D@@ @@@6@@@@@9@@@%@@<( @@@\ * *@); [equal u u'] is [u = u']. ] E E] E e@@@@@@@O@@@9ڐ@@@@@@['compare"_ g k_ g r@б@гh!t_ g u_ g v@@ @@@3@to8@A@@б@гy!t_ g z_ g {@@ @@@@@г٠#int_ g _ g @@ @@@@@@@@!@@@'@@$* @@@_ g g@ * [compare u u'] is [Stdlib.compare u u']. !`  "`  @@@@@@@:P@@@5@@@@@@C+seeded_hash#8b  9b  @б@г#intCb  Db  @@ @@@3EDDEEEEE@\q8@A@@б@гԠ!tTb  Ub  @@ @@@@@г4#intab  bb  @@ @@@@@@@@!@@@'@@$* @@@ob  @ߐ [seeded_hash seed u] A seeded hash function with the same output value as {!Hashtbl.seeded_hash}. This function allows this module to be passed as an argument to the functor {!Hashtbl.MakeSeeded}. @since 5.3 |c  }g  @@@@@@@Q@@@@@@@@@C$hash$i  i  @б@г!ti  i  @@ @@@3@\q8@A@@г#inti  i  @@ @@@@@@@@@@@i   @( 5 An unseeded hash function with the same output value as {!Hashtbl.hash}. This function allows this module to be passed as an argument to the functor {!Hashtbl.Make}. @before 5.3 The hashing algorithm was different. Use [Hashtbl.rebuild] for stored tables which used this hashing function j  o  @@@@@@@R@@@8ِ@@@@@@1搠 + {1:utf UTF codecs tools} @since 4.14 q  s);@@@@@@3@CX1@AA+*utf_decode%Bu=Bu=L@@;@@pA@@@@@u==u=Z@)immediateu=Pu=Y@@u=M @o The type for UTF decode results. Values of this type represent the result of a Unicode Transformation Format decoding attempt.  v[[ w@@@@@@@A@%S@@@A@@#@@@@@@@9+*@3utf_decode_is_valid&'y(y@б@гB*utf_decode2y3y @@ @@@343344444@SMG@A@@г$boolAyBy@@ @@@@@@@@@@@Ly @ P [utf_decode_is_valid d] is [true] if and only if [d] holds a valid decode. YzZ{Zh@@@@@@@rT@@@m@@@@@@10utf_decode_uchar'p}jnq}j~@б@г*utf_decode{}j|}j@@ @@@3}||}}}}}@J_8@A@@г !t}j}j@@ @@@@@@@@@@@}jj @ [utf_decode_uchar d] is the Unicode character decoded by [d] if [utf_decode_is_valid d] is [true] and {!Uchar.rep} otherwise. ~@@@@@@@U@@@@@@@@@11utf_decode_length(0@б@гԠ*utf_decode3=@@ @@@3@J_8@A@@г#intAD@@ @@@@@@@@@@@ @N I [utf_decode_length d] is the number of elements from the source that were consumed by the decode [d]. This is always strictly positive and smaller or equal to [4]. The kind of source elements depends on the actual decoder; for the decoders of the standard library this function always returns a length in bytes. EEU@@@@@@@V@@@^@@@@@@1*utf_decode)@б@гࠐ#int @@ @@@3@J_8@A@@б@г!t@@ @@@@@г;*utf_decode+,@@ @@@@@@@@!@@@'@@$* @@@9@ [utf_decode n u] is a valid UTF decode for [u] that consumed [n] elements from the source for decoding. [n] must be positive and smaller or equal to [4] (this is not checked by the module). FGF@@@@@@@_W@@@Z@@@@@@C2utf_decode_invalid*]^@б@г;#inthi@@ @@@3jiijjjjj@\q8@A@@г*utf_decodewx@@ @@@@@@@@@@@ @򐠠  [utf_decode_invalid n] is an invalid UTF decode that consumed [n] elements from the source to error. [n] must be positive and smaller or equal to [4] (this is not checked by the module). The resulting decode has {!rep} as the decoded Unicode character. @@@@@@@X@@@@@@@@@1;utf_8_decode_length_of_byte+@б@г$char@@ @@@3@J_8@A@@г#int@@ @@@@@@@@@@@ @; [utf_8_decode_length_of_byte byte] is the number of bytes, from 1 to {!max_utf_8_decode_length}, that a valid UTF-8 decode starting with byte [byte] would consume or [0] if [byte] cannot start a valid decode. @since 5.4 @@@@@@@Y@@@K쐠@@@@@@17max_utf_8_decode_length,@гˠ#int @@ @@@3@H]6@A@@@  @r [max_utf_8_decode_length] is [4], the maximal number of bytes a valid or invalid UTF-8 decode can consume. @since 5.4     @@@@@@@ (Z@@@ #@@@@@@!1utf_8_byte_length- & '@б@г!t 1 2@@ @@@3 3 2 2 3 3 3 3 3@:M8@A@@г #int @ A@@ @@@@@@@@@@@ K @ Q [utf_8_byte_length u] is the number of bytes needed to encode [u] in UTF-8.  X Y @@@@@@@ q[@@@ l@@@@@@12utf_16_byte_length. o  p "@б@г!t z % { &@@ @@@3 | { { | | | | |@J_8@A@@г \#int  *  -@@ @@@@@@@@@@@    @ S [utf_16_byte_length u] is the number of bytes needed to encode [u] in UTF-16.  .. q@@@@@@@ \@@@ @@@@@@1@60A@@@@_J@*@@u@U.@@@wP@0 @@j@P@@g@G @A@@pI@)@@b@B@@@X@@3        @lZ@A@ H************************************************************************ A@@ A@L@ H  BMM BM@ H OCaml  C C@ H  D D3@ H Daniel C. Buenzli  E44 E4@ H  F F@ H Copyright 2014 Institut National de Recherche en Informatique et  G G@ H en Automatique.  H Hg@ H  Ihh !Ih@ H All rights reserved. This file is distributed under the terms of  &J 'J@ H the GNU Lesser General Public License version 2.1, with the  ,K -KN@ H special exception on linking described in the file LICENSE.  2LOO 3LO@ H  8M 9M@ H************************************************************************ >N ?N5@ '* Unicode characters. @since 4.03  D * The type for Unicode characters. A value of this type represents a Unicode {{:http://unicode.org/glossary/#unicode_scalar_value}scalar value} which is an integer in the ranges [0x0000]...[0xD7FF] or [0xE000]...[0x10FFFF]. 3* [min] is U+0000. p5* [max] is U+10FFFF. < * [bom] is U+FEFF, the {{:http://unicode.org/glossary/#byte_order_mark}byte order mark} (BOM) character. @since 4.06  ~* [rep] is U+FFFD, the {{:http://unicode.org/glossary/#replacement_character}replacement} character. @since 4.06 Ԡ * [succ u] is the scalar value after [u] in the set of Unicode scalar values. @raise Invalid_argument if [u] is {!max}.  * [pred u] is the scalar value before [u] in the set of Unicode scalar values. @raise Invalid_argument if [u] is {!min}. H * [is_valid n] is [true] if and only if [n] is a Unicode scalar value (i.e. in the ranges [0x0000]...[0xD7FF] or [0xE000]...[0x10FFFF]). n* [of_int i] is [i] as a Unicode character. @raise Invalid_argument if [i] does not satisfy {!is_valid}. #*/*#*/*c #* [to_int u] is [u] as an integer. * H* [is_char u] is [true] if and only if [u] is a latin1 OCaml character. 䠠 -* [of_char c] is [c] as a Unicode character.  t* [to_char u] is [u] as an OCaml latin1 character. @raise Invalid_argument if [u] does not satisfy {!is_char}. X#*/*=#*/*<* [equal u u'] is [u = u'].  +* [compare u u'] is [Stdlib.compare u u']. \ * [seeded_hash seed u] A seeded hash function with the same output value as {!Hashtbl.seeded_hash}. This function allows this module to be passed as an argument to the functor {!Hashtbl.MakeSeeded}. @since 5.3  6* An unseeded hash function with the same output value as {!Hashtbl.hash}. This function allows this module to be passed as an argument to the functor {!Hashtbl.Make}. @before 5.3 The hashing algorithm was different. Use [Hashtbl.rebuild] for stored tables which used this hashing function  ,* {1:utf UTF codecs tools} @since 4.14  * The type for UTF decode results. Values of this type represent the result of a Unicode Transformation Format decoding attempt. } Q* [utf_decode_is_valid d] is [true] if and only if [d] holds a valid decode. 3 * [utf_decode_uchar d] is the Unicode character decoded by [d] if [utf_decode_is_valid d] is [true] and {!Uchar.rep} otherwise.  J* [utf_decode_length d] is the number of elements from the source that were consumed by the decode [d]. This is always strictly positive and smaller or equal to [4]. The kind of source elements depends on the actual decoder; for the decoders of the standard library this function always returns a length in bytes.  * [utf_decode n u] is a valid UTF decode for [u] that consumed [n] elements from the source for decoding. [n] must be positive and smaller or equal to [4] (this is not checked by the module). O  * [utf_decode_invalid n] is an invalid UTF decode that consumed [n] elements from the source to error. [n] must be positive and smaller or equal to [4] (this is not checked by the module). The resulting decode has {!rep} as the decoded Unicode character.  * [utf_8_decode_length_of_byte byte] is the number of bytes, from 1 to {!max_utf_8_decode_length}, that a valid UTF-8 decode starting with byte [byte] would consume or [0] if [byte] cannot start a valid decode. @since 5.4 à * [max_utf_8_decode_length] is [4], the maximal number of bytes a valid or invalid UTF-8 decode can consume. @since 5.4  R* [utf_8_byte_length u] is the number of bytes needed to encode [u] in UTF-8. I T* [utf_16_byte_length u] is the number of bytes needed to encode [u] in UTF-16. @?)../ocamlc0-strict-sequence(-absname"-w5+a-4-9-41-42-44-45-48"-g+-warn-error"+A*-bin-annot)-nostdlib*-principal"-o1stdlib__Uchar.cmi"-c  Q/home/ci/builds/workspace/precheck/flambda/false/label/ocaml-ubuntu-latest/stdlib @@0lǾPIC<63        @ @@8CamlinternalFormatBasics0%FU(Q/Tu&Stdlib0Lku]8_٠ ܐ056uf4[_@056uf4[_A]C@ӰS U@n@$~N@>xȐMB| H o@Z#]@(  =@@ W@pz@@$@@_@@ @@P@@