Caml1999I0314-Stdlib__Stack!t8!a@@A@A@O@B@@@)stack.mliUU@@@@@A@ %Empty #exnG@@@A&_none_@@A@AB@&create@$unitF@@@,!a@@@@@@@(\HH)\Ha@@9B@$push@!a@@ @@@$@@@@@@@@A_B_@@RC@#pop@-!a@@@@@@@TbUb@@eD@'pop_opt@@!a@@@@&optionJ @@@@@@nfvvofv@@E@#top@Z!a@@@@@@@kk/@@F@'top_opt@m!a@@@@- @@@@@@oo@@G@%clear@!a@@@@@@@@@@t((t(@@@H@$copy@!a@@@@@@@@@@wllwl@@I@(is_empty@!a@@@@$boolE@@@@@@zz@@J@&length@̠!a@@@@#intA@@@@@@}  }  (@@ K@$iter@@!a@@@@@@@ @@@@@@@@@@@@ p p@ p @@)L@$fold@@!b@@!a@ @@@@@ @ @@@@@@@@@@7E P P8E P @@HM@&to_seq@#!a@@@@&Stdlib#Seq!t@@@@@@UM l lVM l @@fN@'add_seq@A!a@@@@@ #Seq!t@@@Y@@@@@@@@vR  wR  "@@O@&of_seq@7#Seq!t!a@@@@n@@@@@@V w wV w @@P@@_L-Stdlib__Stack0'#ߓZM,+Stdlib__Seq0yt\eǟ&Q,}.Stdlib__Either0 }rCT0J){9)&Stdlib0>,W:(8CamlinternalFormatBasics0cEXyU?U@А!a@0EDDEEEEE@D8@@@A@A@G@B@@@QU@)ocaml.docb 6 The type of stacks containing elements of type ['a]. _V`V@@@@@@@@@w@@AcUdU@@B@@8#@A@A@O@B@@@@@ @@A@@g,@%Empty BtXuX@ @@@AyX@( H Raised when {!Stack.pop} or {!Stack.top} is applied to an empty stack. YYE@@@@@@@A@@@@0@R&@A@&create \HL\HR@б@г$unit\HU\HY@@ @@@0@71@A@@гq!t\H`\Ha@А!a@C@\H]\H_@@@ @@@@@@"@@%@@@\HH@v & Return a new stack, initially empty. ]bb]b@@@@@@@B@'@2$push __@б@А!a@C@0@G\(@A__@@б@г!t__@А!a__@@@@@@ @@гg$unit__@@ @@@(@@@@@+@@@3@@., @@@_@ː : [push x s] adds the element [x] at the top of stack [s]. (`)`@@@@@@@@C@@A#pop4b5b@б@г!t?b@b@А!a@C@0GFFGGGGG@`q2@AMbNb@@@ @@@ @@А!a XbYb@@@ @@@@@_b@ l [pop s] removes and returns the topmost element in stack [s], or raises {!Empty} if the stack is empty. kcldEt@@@@@@@D@@%'pop_optwfvzxfv@б@гD!tfvfv@А!a@C@0@D_2@Afvfv@@@ @@@ @@г&optionfvfv@А!afvfv@@@"@@@ @@@@@!@@@fvv@` ~ [pop_opt s] removes and returns the topmost element in stack [s], or returns [None] if the stack is empty. @since 4.08 gi@@@@@@@E@"@4#topkk"@б@г!tk(k)@А!a@C@0@Sn2@Ak%k'@@@ @@@ @@А!a k-k/@@@ @@@@@k@ ` [top s] returns the topmost element in stack [s], or raises {!Empty} if the stack is empty. l00mf@@@@@@@F@@%'top_opt o o@б@г٠!too@А!a@C@0@D_2@A%o&o@@@ @@@ @@г&option3o4o@А!a:o;o@@@"@@@ @@@@@!@@@Fo@ j [top_opt s] returns the topmost element in stack [s], or [None] if the stack is empty. @since 4.08 RpSr&@@@@@@@jG@"@4%clear^t(,_t(1@б@г+!tit(7jt(8@А!a@C@0qppqqqqq@Sn2@Awt(4xt(6@@@ @@@ @@гޠ$unitt(<t(@@@ @@@@@@@@@@@t(( @? $ Discard all elements from a stack. uAAuAj@@@@@@@H@@,$copywlpwlt@б@гu!twlzwl{@А!a@C@0@Kf2@Awlwwly@@@ @@@ @@г!twlwl@А!awlwl@@@"@@@ @@@@@!@@@wll@ # Return a copy of the given stack. xx@@@@@@@I@"@4(is_emptyzz@б@гǠ!tzz@А!a@C@0        @Sn2@Azz@@@ @@@ @@г$bool!z"z@@ @@@@@@@@@@@,z @ې ? Return [true] if the given stack is empty, [false] otherwise. 8{9{ @@@@@@@PJ@@,&lengthD}  E}  @б@г!tO}  P}  !@А!a@C@0WVVWWWWW@Kf2@A]}  ^}  @@@ @@@ @@г#intk}  %l}  (@@ @@@@@@@@@@@v}   @% @ Return the number of elements in a stack. Time complexity O(1) ~ ) )~ ) n@@@@@@@K@@,$iter@ p t@ p x@б@б@А!a@C@0@C^*@A@ p |@ p ~@@г$unit@ p @ p @@ @@@@@@@@@@б@г|!t@ p @ p @А!a)$@ p @ p @@@/@@@+ @@г($unit@ p @ p @@ @@@8@@@@@;@@@,@@>@ p { @@@@ p p@ [iter f s] applies [f] in turn to all elements of [s], from the element at the top of the stack to the element at the bottom of the stack. The stack itself is unchanged. A  C  N@@@@@@@L@@R$foldE P TE P X@б@б@А!b@C@0@i|*@AE P \E P ^@@б@А!a@C@E P bE P d@@А!bE P hE P j@@@@@ @@@"@@@@б@А!b(#(E P o)E P q@@б@г!t3E P x4E P y@А!a+5:E P u;E P w@@@1@@@< @@А!bE@EE P }FE P @@@ J@@E@@@M@@H%@@@0@@KPE P [ @@@SE P P@ [fold f accu s] is [(f (... (f (f accu x1) x2) ...) xn)] where [x1] is the top of the stack, [x2] the second element, and [xn] the bottom element. The stack is unchanged. @since 4.03 _F  `I 7 I@@@@@@@wM@@_u: {1 Stacks and Sequences} pK K KqK K j@@@@@@0onnooooo@o#@A&to_seqS|M l p}M l v@б@гI!tM l |M l }@А!a@C@ M l yM l {@@@ @@@'@@гl#Seq!tM l M l @А!a8M l M l @@@#@@@? @@@@@B"@@@M l l@f k Iterate on the stack, top to bottom. It is safe to modify the stack during iteration. @since 4.07 N  P  @@@@@@@N@"@U'add_seqTR  R  @б@г!tR  R  @А!a@C@0@to2@AR  R  @@@ @@@ @@б@г#Seq!tR  R  @А!a!R  R  @@@'@@@# @@гi$unitR  R  "@@ @@@0@@@@@3@@@1@@64 @@@R  @͐ M Add the elements from the sequence on the top of the stack. @since 4.07 *S # #+T c u@@@@@@@BO@@I&of_seqU6V w {7V w @б@г #Seq!tDV w EV w @А!a@ C@ 0LKKLLLLL@k5@ARV w SV w @@@ @@@  @@г"!t`V w aV w @А!agV w hV w @@@"@@@  @@@@@ !@@@sV w w@" 3 Create a stack from the sequence. @since 4.07 W  X  @@@@@@@P@"@4@KA@B@@q@]0@@@O@;@@o@['@@N@)@@s4@@0@Wu6@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@ c* Last-in first-out stacks. This module implements stacks (LIFOs), with in-place modification.  7* The type of stacks containing elements of type ['a].  I* Raised when {!Stack.pop} or {!Stack.top} is applied to an empty stack.  '* Return a new stack, initially empty. 5 ;* [push x s] adds the element [x] at the top of stack [s]. 㠠 m* [pop s] removes and returns the topmost element in stack [s], or raises {!Empty} if the stack is empty.  * [pop_opt s] removes and returns the topmost element in stack [s], or returns [None] if the stack is empty. @since 4.08 T a* [top s] returns the topmost element in stack [s], or raises {!Empty} if the stack is empty.  k* [top_opt s] returns the topmost element in stack [s], or [None] if the stack is empty. @since 4.08 Š %* Discard all elements from a stack. ~ $* Return a copy of the given stack. / @* Return [true] if the given stack is empty, [false] otherwise. 蠠 A* Return the number of elements in a stack. Time complexity O(1)  * [iter f s] applies [f] in turn to all elements of [s], from the element at the top of the stack to the element at the bottom of the stack. The stack itself is unchanged. < * [fold f accu s] is [(f (... (f (f accu x1) x2) ...) xn)] where [x1] is the top of the stack, [x2] the second element, and [xn] the bottom element. The stack is unchanged. @since 4.03 ʠ;* {1 Stacks and Sequences}  l* Iterate on the stack, top to bottom. It is safe to modify the stack during iteration. @since 4.07 l N* Add the elements from the sequence on the top of the stack. @since 4.07  4* Create a stack from the sequence. @since 4.07 @D)../ocamlc0-strict-sequence(-absname"-w8+a-4-9-41-42-44-45-48-70"-g+-warn-error"+A*-bin-annot)-nostdlib*-principal,-safe-string/-strict-formats"-o1stdlib__Stack.cmi"-cDE 1/home/barsac/ci/builds/workspace/bootstrap/stdlib @0{@TiPY_Ok0HGGHHHHH@F@@8CamlinternalFormatBasics0cEXy,W:(.Stdlib__Either0 }rCT0J){9)+Stdlib__Seq0yt\eǟ&Q,}w0'#ߓZM,@0'#ߓZM,AQ@ @@@32@lk@~@@@@@GF@JI@@ @#"(@@@P@