Caml1999I037  j F.Stdlib__Either!t&;!a@!b@~@B$Left@@*either.mlix  x  @@A@%Right@@ x   x  @@&B@@@A@YY@@@@@@x  @@@@-@@A@$left'@!a@8!b@@@@@@@+| G G,| G b@@FC@@%right(@!b@!a@ @@@@@@C  D  @@^D@@'is_left)@-!a@!b@@@@$boolE@@@@@@aB  bB  @@|E@@(is_right*@K!a@!b@@@@@@@@@@}E % %~E % F@@F@@(get_left+@g!a@!b@@@@ @@@H  H  @@G@@)get_right,@!a@!b@@@@@@@O 5 5O 5 U@@H@@)find_left-@!a@!b@@@@&optionL@@@@@@V  V  @@I@@*find_right.@!a@!b@@@@ @@@@@@Y O OY O w@@J@@(map_left/@@"a1@"a2@@@@ߠ !b@@@@ @@@@@@@@\  \  @@)K@@)map_right0@@"b1@"b2@@@@!a@@@@  @@@@@@@@3`YY4`Y@@NL@@#map1$left@"a1@"a2@@@%right@"b1@"b2@@@@9@@@>@@@@@@@@@@ddeeD@@M@@$fold2$left@!a@!c@@@%right@!b@@@@f @@@@@@@@@@ii@@N@@'retract3@v!a@ɠ@@@@@@m]]m]{@@O@@$iter4$left@!a@$unitF@@@@@%right@!b@@@@@@@@@@@@@@@@@@@@rr@@P@@'for_all5$left@!a@@@@@@%right@!b@@@@@@@ؠ@@@@@@@@@@@@@v~~v~@@Q@@%equal6$left@!a@@@@@@@@@%right@!b@@@@@@@@@@ @@@@&@@@@@@@@@@@@@@@=z66>|{@@XR@@'compare7$left@!a@@#intA@@@@@@@%right@!b@@@@@@@@@@I!@@@@P(@@@$@@@@@@@@@@@@zDD{@@S@@@l:..Stdlib__Either0Vy`u~c à&Stdlib0Lku]8_٠8CamlinternalFormatBasics0%FU(Q/Tu@@@Caml1999T037U9 41C.Stdlib__Either*ocaml.text&_none_@@A  Either type. Either is the simplest and most generic sum/variant type: a value of [('a, 'b) Either.t] is either a [Left (v : 'a)] or a [Right (v : 'b)]. It is a natural choice in the API of generic functions where values could fall in two different cases, possibly at different types, without assigning a specific meaning to what each case should be. For example: {[List.partition_map: ('a -> ('b, 'c) Either.t) -> 'a list -> 'b list * 'c list]} If you are looking for a parametrized type where one alternative means success and the other means failure, you should use the more specific type {!Result.t}. @since 4.12 *either.mliP77d@@@@@@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+!tAx  x  @А!a@3@;@@@@@B@A@GG@BB@@@x  x  @)ocaml.doc X A value of [('a, 'b) Either.t] contains either a value of ['a] or a value of ['b] y  z  E@@@@@@@@@@@@Ax  x  @@BAА!b@.x  x  @@ @;6 @B$Left@B@@@x  x  @@A@%RightB@@@x  ;@@B@@@A@YY@@@@@@B?@@/@#x  @@А!a [x  @@@@ @#x  x  @@А!b!hx  Z@@@@!@@A@\YXW@WW@@@W@W@@gf@$left| G K | G O@б@А!a@B@3@[@A| G R| G T@@г!t | G a!| G b@А!a'| G Y(| G [@@А!b@B@3| G ]4| G _@@@) @@@&;| G X@@@/ @@*(@@@A| G G!@7 [left v] is [Left v]. N} c cO} c @@@@@@@gC@@1@b@@@@@@I%righte  f  @б@А!b@B@3nmmnnnnn@^o4@At  u  @@г!t}  ~  @А!a@B@    @@А!b#    @@@*@@@&  @@@/ @@*(@@@  !@9 [right v] is [Right v]. @  @  @@@@@@@D@@1@@@@@@@I'is_leftB  B  @б@гM!tB  B  @А!a@B@3@hy>@AB  B  @@А!b@B@B  B  @@@# @@@B  "@@г$boolB  B  @@ @@@$@@@@@'@@@B   @h ? [is_left (Left v)] is [true], [is_left (Right v)] is [false]. C  C  #@@@@@@@(E@@@x#@@@@@@F(is_right&E % )'E % 1@б@г!t1E % =2E % >@А!a@B@398899999@e>@A?E % 5@E % 7@@А!b@B@KE % 9LE % ;@@@# @@@SE % 4"@@г$bool[E % B\E % F@@ @@@$@@@@@'@@@fE % % @̐ A [is_right (Left v)] is [false], [is_right (Right v)] is [true]. sF G GtF G @@@@@@@F@@@@@@@@@F(get_leftH  H  @б@г!tH  H  @А!a@B@3@e>@AH  H  @@А!b@B@H  H  @@@# @@@H  "@@А!a H  H  @@@%@@  @@@H  @)  [get_left e] is [v] if [e] is [Left v] and raise otherwise. @raise Invalid_argument if [e] is [Right _]. @since 5.4 I  M " 3@@@@@@@G@@@9䐠@@@@@@?)get_rightO 5 9O 5 B@б@гr!tO 5 NO 5 O@А!a@B@3@^y>@AO 5 FO 5 H@@А!b@B@ O 5 J O 5 L@@@# @@@O 5 E"@@А!bO 5 SO 5 U@@@@@  @@@ O 5 5@ [get_right e] is [v] if [e] is [Right v] and raise otherwise. @raise Invalid_argument if [e] is [Left _]. @since 5.4 -P V V.T  @@@@@@@FH@@@A@@@@@@?)find_leftDV  EV  @б@гϠ!tOV  PV  @А!a@B@3WVVWWWWW@^y>@A]V  ^V  @@А!b@B@iV  jV  @@@# @@@qV  "@@гؠ&optionyV  zV  @А!a*%V  V  @@@0@@@, @@@@@/@@@V  @򐠠 C [find_left (Left v)] is [Some v], [find_left (Right _)] is [None] W  W  M@@@@@@@I@@#@@@@@@@N*find_rightY O SY O ]@б@г;!tY O iY O j@А!a@B@3@m>@AY O aY O c@@А!b@B@Y O eY O g@@@# @@@Y O `"@@гD&optionY O qY O w@А!b%Y O nY O p@@@"@@@, @@@@@/@@@Y O O@^ E [find_right (Right v)] is [Some v], [find_right (Left _)] is [None] Z x xZ x @@@@@@@J@@#@n@@@@@@N(map_left\  \  @б@б@А"a1@B@3'&&'''''@e6@A-\  .\  @@А"a2@B@ 8\  9\  @@@ @@ @@б@гƠ!tF\  G\  @А"a1'"M\  N\  @@А!b@B@ .Y\  Z\  @@@9 @@@ 6a\  @@г預!ti\  j\  @А"a2=Ep\  q\  @@А!b#Lw\  x\  @@@J*@@@T\  @@@' @@X"@@@K@@[\  @@@\   @ T [map_left f e] is [Left (f v)] if [e] is [Left v] and [e] if [e] is [Right _]. ]  ^4W@@@@@@@K@@0@@@@@@@{)map_right`Y]`Yf@б@б@А"b1@(B@3@6@A`Yj`Ym@@А"b2@*B@ `Yq`Yt@@@ @@@@б@гW!t`Y`Y@А!a@&B@'`Yz`Y|@@А"b13.`Y~`Y@@@:@@@6`Yy@@гz!t`Y`Y@А!a#E`Y`Y@@А"b2DL`Y `Y@@@0K@@@"T`Y@@@' @@#X"@@@K@@$[`Yi@@@`YY @ V [map_right f e] is [Right (f v)] if [e] is [Right v] and [e] if [e] is [Left _]. 'a(b@@@@@@@@L@@0@;@@@@@@{#map>d?d@б$leftб@А"a1@;B@+3KJJKKKKK@8@AQeRe@@А"a2@=B@, \e ]e @@@ @@-@@б%rightб@А"b1@?B@.!peqe@@А"b2@AB@/,{e |e#@@@ @@01@@б@г !te3e4@А"a1FAe)e,@@А"b1,He.e1@@@S3@@@3Pe(@@г'!teCeD@А"a2W_e9e<@@А"b2?fe>eA@@@dF@@@6ne8@@@' @@7r"@@`F@@8ue@@i@@9ye!@@@d$@1 h [map ~left ~right (Left v)] is [Left (left v)], [map ~left ~right (Right v)] is [Right (right v)]. fEEgy@@@@@@@M@@4@A쐠@@@@@@$fold ii@б$leftб@А!a@NB@B3@8@Aii@@А!c@RB@C  ii@@@ @@D@@б%rightб@А!b@PB@E!!i"i@@А!c''i(i@@@$@@F, @@б@г!t5i6i@А!aA<<i=i@@А!b'CCiDi@@@N.@@@IKKi@@А!cHPPiQi@@@M@@JU @@C.@@KXXi@@hL@@L\\i @@@_i@Ő _ [fold ~left ~right (Left v)] is [left v], and [fold ~left ~right (Right v)] is [right v]. ljmk)[@@@@@@@N@@@@@@@@@|'retract!m]am]h@б@г!tm]tm]u@А!a@YB@S3@>@Am]lm]n@@А!a m]pm]r@@@@@@Vm]k@@А!am]ym]{@@@ @@W @@@m]]@ L [retract (Left v)] is [v], and [retract (Right v)] is [v]. @since 5.4 n||p@@@@@@@O@@@-ؐ@@@@@@:$iter"rr@б$leftб@А!a@hB@Z3@Sn8@Arr@@г$unitrr@@ @@@[@@@@@\@@б%rightб@А!b@jB@]#rr@@гŠ$unitrr@@ @@@^2@@@@@_5@@б@г!t*r+r@А!aJE1r2r@@А!b.L8r 9r @@@W5@@@bT@r@@г$unitHrIr@@ @@@cb@@@@@de@@Q5@@ehTr @@xZ@@flXr@@@[r@ _ [iter ~left ~right (Left v)] is [left v], and [iter ~left ~right (Right v)] is [right v]. hsitJ|@@@@@@@P@@#@|@@@@@@'for_all#v~v~@б$leftб@А!a@yB@k3@8@Av~v~@@гY$boolv~v~@@ @@@l@@@@@m@@б%rightб@А!b@{B@n#v~v~@@гz$boolv~v~@@ @@@o2@@@@@p5@@б@гN!tv~v~@А!aJEv~v~@@А!b.Lv~v~@@@W5@@@sTv~@@г$boolv~v~@@ @@@tb@@@@@ue@@Q5@@vhv~ @@xZ@@wlv~@@@v~~@e e [for_all ~left ~right (Left v)] is [left v], and [for_all ~left ~right (Right v)] is [right v].  w x4@@@@@@@ %Q@@#@u @@@@@@%equal$ #z6: $z6?@б$leftб@А!a@B@|3 0 / / 0 0 0 0 0@8@A 6{BJ 7{BL@@б@А!a  >{BP ?{BR@@г $bool G{BV H{BZ@@ @@@}@@@!@@~@@@$@@ @@б%rightб@А!b@B@. b{Bf c{Bh@@б@А!b 6 j{Bl k{Bn@@г 1$bool s{Br t{Bv@@ @@@E@@@@@H@@@"@@K @@б@г!t |{ |{@А!a`[ |{~ |{@@А!b9b |{ |{@@@m@@@@j |{}@@б@г(!t |{ |{@А!a{ |{ |{@@А!bY |{ |{@@@`@@@ |{@@г $bool |{ |{@@ @@@@@@@@@@@9@@4 @@X@@ {B_@@@@ {BD@@@ z66@B [equal ~left ~right e0 e1] tests equality of [e0] and [e1] using [left] and [right] to respectively compare values wrapped by [Left _] and [Right _].  } 1B@@@@@@@ R@@&@R @@@@@@'compare% DH DO@б$leftб@А!a@B@3        @8@A RZ R\@@б@А!a  R` Rb@@г #int $Rf %Ri@@ @@@@@@!@@@@@$@@ @@б%rightб@А!b@B@. ?Ru @Rw@@б@А!b 6 GR{ HR}@@г ##int PR QR@@ @@@E@@@@@H@@@"@@K @@б@г堐!t e f@А!a`[ l m@@А!b9b s t@@@m@@@@j {@@б@г !t  @А!a{  @@А!bY  @@@`@@@ @@г v#int  @@ @@@@@@@@@@@9@@4 @@X@@ Rn@@@@ RT@@@ DD@  [compare ~left ~right e0 e1] totally orders [e0] and [e1] using [left] and [right] to respectively compare values wrapped by [Left _ ] and [Right _]. [Left _] values are smaller than [Right _] values.   I@@@@@@@ S@@&@ / ڐ@@@@@@@ [ A@@z?@@{@[ @@[@;@b@B@$@@r<@@z@@B@@3        @D@A@ H************************************************************************ A@@ A@L@ H  BMM BM@ H OCaml  C C@ H  D D3@ H Gabriel Scherer, projet Parsifal, INRIA Saclay  E44 E4@ H  F F@ H Copyright 2019 Institut National de Recherche en Informatique et  #G $G@ H en Automatique.  )H *Hg@ H  /Ihh 0Ih@ H All rights reserved. This file is distributed under the terms of  5J 6J@ H the GNU Lesser General Public License version 2.1, with the  ;K ('b, 'c) Either.t) -> 'a list -> 'b list * 'c list]} If you are looking for a parametrized type where one alternative means success and the other means failure, you should use the more specific type {!Result.t}. @since 4.12  S  Unlike [result], no [either] type is made available in Stdlib, one needs to access [Either.t] explicitly: - This type is less common in typical OCaml codebases, which prefer domain-specific variant types whose constructors carry more meaning. - Adding this to Stdlib would raise warnings in existing codebases that already use a constructor named Left or Right: + when opening a module that exports such a name, warning 45 is raised + adding a second constructor of the same name in scope kicks in the disambiguation mechanisms, and warning 41 may now be raised by existing code. If the use becomes more common in the future we can always revisit this choice.  Vf Wv  @!* \x   ]x  @ Y* A value of [('a, 'b) Either.t] contains either a value of ['a] or a value of ['b]  8* [left v] is [Left v].  :* [right v] is [Right v].  @* [is_left (Left v)] is [true], [is_left (Right v)] is [false]. \ B* [is_right (Left v)] is [false], [is_right (Right v)] is [true].  * [get_left e] is [v] if [e] is [Left v] and raise otherwise. @raise Invalid_argument if [e] is [Right _]. @since 5.4  * [get_right e] is [v] if [e] is [Right v] and raise otherwise. @raise Invalid_argument if [e] is [Left _]. @since 5.4 G D* [find_left (Left v)] is [Some v], [find_left (Right _)] is [None] ޠ F* [find_right (Right v)] is [Some v], [find_right (Left _)] is [None] u U* [map_left f e] is [Left (f v)] if [e] is [Left v] and [e] if [e] is [Right _]. 砠 W* [map_right f e] is [Right (f v)] if [e] is [Right v] and [e] if [e] is [Left _]. Y i* [map ~left ~right (Left v)] is [Left (left v)], [map ~left ~right (Right v)] is [Right (right v)].  `* [fold ~left ~right (Left v)] is [left v], and [fold ~left ~right (Right v)] is [right v].  M* [retract (Left v)] is [v], and [retract (Right v)] is [v]. @since 5.4 Š `* [iter ~left ~right (Left v)] is [left v], and [iter ~left ~right (Right v)] is [right v]. $ f* [for_all ~left ~right (Left v)] is [left v], and [for_all ~left ~right (Right v)] is [right v].  * [equal ~left ~right e0 e1] tests equality of [e0] and [e1] using [left] and [right] to respectively compare values wrapped by [Left _] and [Right _].  * [compare ~left ~right e0 e1] totally orders [e0] and [e1] using [left] and [right] to respectively compare values wrapped by [Left _ ] and [Right _]. [Left _] values are smaller than [Right _] values. @?)../ocamlc0-strict-sequence(-absname"-w5+a-4-9-41-42-44-45-48"-g+-warn-error"+A*-bin-annot)-nostdlib*-principal"-o2stdlib__Either.cmi"-c  D/builds/workspace/precheck/flambda/false/label/ocaml-linux-32/stdlib @@0uQGIiwi3        @ @@8CamlinternalFormatBasics0%FU(Q/Tu&Stdlib0Lku]8_٠ ͐0Vy`u~c @0Vy`u~c ATCA@Ր'   g@@ x @@H@@԰):@ ) Z@@ѐ.e@@    @Ґgx v@@@@P@@