Caml1999I0372#Str®exp4;@@@A@@@@@'str.mliZ##Z#.@@@@ @@A@®exp5@&stringQ@@@@@@@@@@@^bb^b@@#A@@0regexp_case_fold6@@@@ @@!@@@"@@#@,NZZ-NZ@@7B@@%quote7@+@@@$@@%/@@@&@@'@AS**BS*F@@LC@@-regexp_string8@@@@@(@@)>@@@*@@+@UWVW@@`D@@7regexp_string_case_fold9@T@@@,@@-R@@@.@@/@i[00j[0^@@tE@@,string_match:@b@@@0@@1@o@@@2@@3@#intA@@@4@@5$boolE@@@6@@7@@8@@9@c  c <@@F@@.search_forward;@@@@:@@;@@@@<@@=@(@@@>@@?,@@@@@@A@@B@@C@hh8@@G@@/search_backward<@@@@D@@E@@@@F@@G@L@@@H@@IP@@@J@@K@@L@@M@pyypy@@H@@4string_partial_match=@@@@N@@O@@@@P@@Q@p@@@R@@Sn@@@T@@U@@V@@W@x  x C@@I@@.matched_string>@@@@X@@Y@@@Z@@[@}}@@J@@/match_beginning?@$unitF@@@\@@]@@@^@@_@)*@@4K@@)match_end@@@@@`@@a@@@b@@c@>?@@IL@@-matched_groupA@@@@d@@e@E@@@f@@gI@@@h@@i@@j@[\@@fM@@/group_beginningB@@@@k@@l@@@m@@n@pq@@{N@@)group_endC@@@@o@@p@@@q@@r@    @@O@@.global_replaceD@~@@@s@@t@@@@u@@v@@@@w@@x@@@y@@z@@{@@|@"""#@@P@@-replace_firstE@@@@}@@~@@@@@@@@@@@@@@@@@@@@@@$$$$@@Q@@1global_substituteF@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@%k%k%k%@@R@@0substitute_firstG@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@%&&&&'1@@0S@@/replace_matchedH@$@@@@@@,@@@@@0@@@@@@@@B''C''@@MT@@%splitI@;@@@@@@H@@@@@$listKR@@@@@@@@@@@e))f))@@pU@@-bounded_splitJ@^@@@@@@k@@@@@@@@@@@+{@@@@@@@@@@@@@***+.@@V@@+split_delimK@@@@@@@@@@@@L@@@@@@@@@@@++++@@W@@3bounded_split_delimL@@@@@@@@@@@@@F@@@@@u@@@@@@@@@@@@@----P@@X@@,split_resultM;@@$Text,@@@@@ ..  ...@@Z@%Delim-@@@@@ ./.1 ./.B@@[@@@A@@@@@..@@@@Y@A@*full_splitN@@@@@@@@@@@@>@@@@@@@@@@@ .D.D .D.z@@)\@@2bounded_full_splitO@@@@@@@$@@@@@@@@@@@)@@@@@@@@@@@@@F//G//@@Q]@@-string_beforeP@E@@@@@@@@@@@Q@@@@@@@@c00d01 @@n^@@,string_afterQ@b@@@@@@@@@@@n@@@@@@@@#11#11@@_@@+first_charsR@@@@@@@@@@@@@@@@@@@@(2v2v(2v2@@`@@*last_charsS@@@@@@@-@@@@@@@@@@@@@,33,33A@@a@@@a7-#Str0݅-d6B2&Stdlib0t0VoS%{<F:8CamlinternalFormatBasics0|.e1R$|o@@@Caml1999T037RoFC#Str*ocaml.text&_none_@@A 6 Regular expressions and high-level string processing 'str.mliP77P7r@@@@@@3@@@@@@#intA;@@#intA@@@@@;@A@$charB;@@$charA@@@@@A@A@&stringQ;@@&stringA@@@@@G@@@%bytesC;@@%bytesA@@@@@M@@@%floatD;@@%floatA@@@@@S@@@$boolE;@@%falsec@@]@$trued@@c@@@A@@@@@d@A@$unitF;@@"()e@@n@@@A@@@@@o@A@ #exnG;@@@A@@@@@s@@@#effH;@@O@A@A@@@@@@|@@@,continuationI;@@Q@@P@B,continuationA@nY@@@@@@@@@%arrayJ;@@R@A%arrayA@@@@@@@@@ $listK;@@S@A"[]f@@@"::g@@@T@@@ @@A@Y@@@@@@@@&optionL;@@V@A$Noneh@@@$Somei@@@@@A@Y@@@@@@@@)nativeintM;@@)nativeintA@@@@@@@@%int32N;@@%int32A@@@@@@@@%int64O;@@%int64A@@@@@@@@&lazy_tP;@@X@A&lazy_tA@Y@@@@@@@@ 5extension_constructorR;@@5extension_constructorA@@@@@@@@*floatarrayS;@@*floatarrayA@@@@@@@@&iarrayT;@@Y@A&iarrayA@Y@@@@@@@@ *atomic_locU;@@Z@A*atomic_locA@@@@@@ @@@ .Assert_failure`#@@@@@J@@@@@@@@[@@A!=ocaml.warn_on_literal_pattern%@&@0Division_by_zero]#@@@A+ . .@+End_of_file\#$@@@A366@'FailureY#,@'@@A<??@0Invalid_argumentX#5@0@@AE$H#H@-Match_failureV#>@@=@9@;@@a@@AV5Y4Y@)Not_foundZ#O@@@A^=a<a@-Out_of_memoryW#W@@@AfEiDi@.Stack_overflow^#_@@@AnMqLq@.Sys_blocked_io_#g@@@AvUyTy@)Sys_error[#o@j@@A^]@:Undefined_recursive_modulea#x@@w@s@u@@h@@Aon@:Continuation_already_takenb#@@@Awv@&Stdlib@A9 {1 Regular expressions} SuuSu@@@@@@ The {!Str} library provides regular expressions on sequences of bytes. It is, in general, unsuitable to match Unicode characters. UX!@@@@@@A+®expAZ#(Z#.@@;@@@A@@@@@Z##@)ocaml.docԐ + The type of compiled regular expressions. [//[/_@@@@@@@@@@@@@A@䐠@@@@@@@ܰ"@®exp^bf^bl@б@г&string^bo^bu@@ @@@{3@A;@A@@гE®exp^by^b@@ @@@|@@@@@}@@~ @@@^bb @M  Compile a regular expression. The following constructs are recognized: - [. ] Matches any character except newline. - [* ] (postfix) Matches the preceding expression zero, one or several times - [+ ] (postfix) Matches the preceding expression one or several times - [? ] (postfix) Matches the preceding expression once or not at all - [[..] ] Character set. Ranges are denoted with [-], as in [[a-z]]. An initial [^], as in [[^0-9]], complements the set. To include a [\]] character in a set, make it the first character of the set. To include a [-] character in a set, make it the first or the last character of the set. - [^ ] Matches at beginning of line: either at the beginning of the matched string, or just after a '\n' character. - [$ ] Matches at end of line: either at the end of the matched string, or just before a '\n' character. - [\| ] (infix) Alternative between two expressions. - [\(..\)] Grouping and naming of the enclosed expression. - [\1 ] The text matched by the first [\(...\)] expression ([\2] for the second expression, and so on up to [\9]). - [\b ] Matches word boundaries. - [\ ] Quotes special characters. The special characters are [$^\.*+?[]]. In regular expressions you will often use backslash characters; it's easier to use a quoted string literal [{|...|}] to avoid having to escape backslashes. For example, the following expression: {[ let r = Str.regexp {|hello \([A-Za-z]+\)|} in Str.replace_first r {|\1|} "hello world" ]} returns the string ["world"]. If you want a regular expression that matches a literal backslash character, you need to double it: [Str.regexp {|\\|}]. You can use regular string literals ["..."] too, however you will have to escape backslashes. The example above can be rewritten with a regular string literal as: {[ let r = Str.regexp "hello \\([A-Za-z]+\\)" in Str.replace_first r "\\1" "hello world" ]} And the regular expression for matching a backslash becomes a quadruple backslash: [Str.regexp "\\\\"]. _L)X@@@@@@@5A@@@]0@@@@@@30regexp_case_fold3NZ^4NZn@б@г&string>NZq?NZw@@ @@@3@??@@@@@@La8@A@@г®expMNZ{NNZ@@ @@@@@@@@@@ @@@ZNZZ @ Same as [regexp], but the compiled expression will match text in a case-insensitive way: uppercase and lowercase letters will be considered equivalent. gOhQ(@@@@@@@B@@@{@@@@@@3%quote~S*.S*3@б@гP&stringS*6S*<@@ @@@3@La8@A@@г_&stringS*@S*F@@ @@@@@@@@@@ @@@S** @㐠 U [Str.quote s] returns a regexp string that matches exactly [s] and nothing else. TGGU@@@@@@@C@@@Ɛ@@@@@@3-regexp_stringWW@б@г&stringWW@@ @@@3@La8@A@@г&®expWW@@ @@@@@@@@@@ @@@W @. a [Str.regexp_string s] returns a regular expression that matches exactly [s] and nothing else.XY.@@@@@@@D@@@>@@@@@@37regexp_string_case_fold[04[0K@б@г栐&string[0N [0T@@ @@@3!  !!!!!@La8@A@@гq®exp.[0X/[0^@@ @@@@@@@@@@ @@@;[00 @y x [Str.regexp_string_case_fold] is similar to {!Str.regexp_string}, but the regexp matches in a case-insensitive way. H\__I]@@@@@@@aE@@@\@@@@@@3ji # {1 String matching and searching} f`g`@@@@@@3eddeeeee@EZ1@A,string_matchrc sc @б@г®exp}c ~c #@@ @@@@@б@гS&stringc 'c -@@ @@@)@@б@гn#intc 1c 4@@ @@@8@@г]$boolc 8c <@@ @@@E@@@@@@@J @@@)@@ @@O,@@@=@@ @@T@@@@c  @ [string_match r s start] tests whether a substring of [s] that starts at position [start] matches the regular expression [r]. The first character of a string has position [0], as usual. d==f@@@@@@@F@@'@ @@@@@@s.search_forwardh h@б@г1®exphh @@ @@@3@8@A@@б@гƠ&stringh$h*@@ @@@@@б@г᠐#inth.h1@@ @@@ @@г#inth5h8@@ @@@-@@@@@@@2 @@@)@@ @@7,@@@?@@ @@<B@@@2h@p 9 [search_forward r s start] searches the string [s] for a substring matching the regular expression [r]. The search starts at position [start] and proceeds towards the end of the string. Return the position of the first character of the matched substring. @raise Not_found if no substring matches. ?i99@nHw@@@@@@@XG@@'@S@@@@@@[/search_backwardVpy}Wpy@б@г®expapybpy@@ @@@3cbbccccc@t8@A@@б@г9&stringrpyspy@@ @@@@@б@гT#intpypy@@ @@@ @@гa#intpypy@@ @@@-@@@@@@@2 @@@)@@ @@7,@@@?@@ @@<B@@@pyy@㐠 T [search_backward r s last] searches the string [s] for a substring matching the regular expression [r]. The search first considers substrings that start at position [last] and proceeds towards the beginning of string. Return the position of the first character of the matched substring. @raise Not_found if no substring matches. qv@@@@@@@H@@'@Ɛ@@@@@@[4string_partial_matchx  x !@б@г®expx $x *@@ @@@3@t8@A@@б@г&stringx .x 4@@ @@@@@б@гǠ#intx 8x ;@@ @@@ @@г$boolx ?x C@@ @@@-@@@@@@@2 @@@)@@ @@7,@@@?@@ @@<B@@@x  @V Similar to {!Str.string_match}, but also returns true if the argument string is a prefix of a string that matches. This includes the case of a true complete match. %yDD&{@@@@@@@>I@@'@f9@@@@@@[.matched_string<}=}@б@г&stringG} H}@@ @@@3IHHIIIII@t8@A@@г&stringV}W}@@ @@@@@@@@@@ @@@c} @  [matched_string s] returns the substring of [s] that was matched by the last call to one of the following matching or searching functions: - {!Str.string_match} - {!Str.search_forward} - {!Str.search_backward} - {!Str.string_partial_match} - {!Str.global_substitute} - {!Str.substitute_first} provided that none of the following functions was called in between: - {!Str.global_replace} - {!Str.replace_first} - {!Str.split} - {!Str.bounded_split} - {!Str.split_delim} - {!Str.bounded_split_delim} - {!Str.full_split} - {!Str.bounded_full_split} Note: in the case of [global_substitute] and [substitute_first], a call to [matched_string] is only valid within the [subst] argument, not after [global_substitute] or [substitute_first] returns. The user must make sure that the parameter [s] is the same string that was passed to the matching or searching function. p~q@@@@@@@J@@@@@@@@@3/match_beginning@б@г6$unit@@ @@@3@La8@A@@гt#int@@ @@@@@@@@@@ @@@ @쐠 [match_beginning()] returns the position of the first character of the substring that was matched by the last call to a matching or searching function (see {!Str.matched_string} for details). q@@@@@@@K@@@ϐ@@@@@@3)match_end@б@г$unit@@ @@@3@La8@A@@г#int@@ @@@@@@@@@@ @@@ @7 [match_end()] returns the position of the character following the last character of the substring that was matched by the last call to a matching or searching function (see {!Str.matched_string} for details). @@@@@@@L@@@G@@@@@@3-matched_group@б@г#int()@@ @@@3*))*****@La8@A@@б@г&string9:@@ @@@@@г &stringFG@@ @@@@@@@@@@# @@@+@@ @@(.@@@X@  [matched_group n s] returns the substring of [s] that was matched by the [n]th group [\(...\)] of the regular expression that was matched by the last call to a matching or searching function (see {!Str.matched_string} for details). When [n] is [0], it returns the substring matched by the whole regular expression. The user must make sure that the parameter [s] is the same string that was passed to the matching or searching function. @raise Not_found if the [n]th group of the regular expression was not matched. This can happen with groups inside alternatives [\|], options [?] or repetitions [*]. For instance, the empty string will match [\(a\)*], but [matched_group 1 ""] will raise [Not_found] because the first group itself was not matched. ef@@@@@@@~M@@"@y@@@@@@G/group_beginning |}@б@гZ#int@@ @@@3@`u8@A@@гi#int@@ @@@@@@@@@@ @@@ @ᐠ  [group_beginning n] returns the position of the first character of the substring that was matched by the [n]th group of the regular expression that was matched by the last call to a matching or searching function (see {!Str.matched_string} for details). @raise Not_found if the [n]th group of the regular expression was not matched. @raise Invalid_argument if there are fewer than [n] groups in the regular expression.   @@@@@@@N@@@Đ@@@@@@3)group_end!    @б@г#int    @@ @@@3@La8@A@@г#int    @@ @@@@@@@@@@ @@@   @,  [group_end n] returns the position of the character following the last character of substring that was matched by the [n]th group of the regular expression that was matched by the last call to a matching or searching function (see {!Str.matched_string} for details). @raise Not_found if the [n]th group of the regular expression was not matched. @raise Invalid_argument if there are fewer than [n] groups in the regular expression.   ""@@@@@@@O@@@<@@@@@@31 {1 Replacement} """"@@@@@@3@EZ1@A.global_replace"%""&""@б@гs®exp0""1""@@ @@@@@б@г&string?"#@"#@@ @@@)@@б@г&stringN"# O"#@@ @@@8@@г"&string["#\"#@@ @@@E@@@@@@@J @@@)@@ @@O,@@@=@@ @@T@@@@r""@  [global_replace regexp templ s] returns a string identical to [s], except that all substrings of [s] that match [regexp] have been replaced by [templ]. The replacement template [templ] can contain [\1], [\2], etc; these sequences will be replaced by the text matched by the corresponding group in the regular expression. [\0] stands for the text matched by the whole regular expression. ##$m$@@@@@@@P@@'@@@@@@@s-replace_first#$$$$@б@г䠐®exp$$$$@@ @@@3@8@A@@б@гy&string$$$$@@ @@@@@б@г&string$$$$@@ @@@ @@г&string$$$$@@ @@@-@@@@@@@2 @@@)@@ @@7,@@@?@@ @@<B@@@$$@# u Same as {!Str.global_replace}, except that only the first substring matching the regular expression is replaced. $$%7%i@@@@@@@ Q@@'@3@@@@@@[1global_substitute$ %k%o %k%@б@гW®exp%k%%k%@@ @@@3@t8@A@@б@б@г&string'%k%(%k%@@ @@@@@г&string4%k%5%k%@@ @@@ @@@@@@@% @@б@г&stringH%k%I%k%@@ @@@4@@г&stringU%k%V%k%@@ @@@A@@@@@@@F @@@*@@ @@Ke%k%@@@T@@ @@QW@@@m%k%k@ / [global_substitute regexp subst s] returns a string identical to [s], except that all substrings of [s] that match [regexp] have been replaced by the result of function [subst]. The function [subst] is called once for each matching substring, and receives [s] (the whole text) as argument. z%%{&&@@@@@@@R@@(@@@@@@@p0substitute_first%&&&&@б@гߠ®exp&'&'@@ @@@3@8@A@@б@б@гv&string&' &'@@ @@@@@г&string&'&'@@ @@@ @@@@@@@% @@б@г&string&'!&''@@ @@@4@@г&string&'+&'1@@ @@@A@@@@@@@F @@@*@@ @@K&' @@@T@@ @@QW@@@&&@3 x Same as {!Str.global_substitute}, except that only the first substring matching the regular expression is replaced.  '2'2 '}'@@@@@@@ S@@(@C @@@@@@p/replace_matched& '' ''@б@г렐&string $'' %''@@ @@@3 & % % & & & & &@8@A@@б@г&string 5'' 6''@@ @@@@@г &string B'' C''@@ @@@@@@@@@@# @@@+@@ @@(.@@@ T''@  [replace_matched repl s] returns the replacement text [repl] in which [\1], [\2], etc. have been replaced by the text matched by the corresponding groups in the regular expression that was matched by the last call to a matching or searching function (see {!Str.matched_string} for details). [s] must be the same string that was passed to the matching or searching function.  a'' b)W)p@@@@@@@ zT@@"@ u@@@@@@G  / {1 Splitting}  )s)s )s)@@@@@@3 ~ } } ~ ~ ~ ~ ~@Yn1@A%split' )) ))@б@г٠®exp )) ))@@ @@@@@б@г l&string )) ))@@ @@@)@@г #$list )) ))@г &string )) ))@@ @@@ @@@@@@@ E @@@$@@  @@ J'@@@8@@ @@O;@@@ ))!@ 7 [split r s] splits [s] into substrings, taking as delimiters the substrings that match [r], and returns the list of substrings. For instance, [split (regexp "[ \t]+") s] splits [s] into blank-separated words. An occurrence of the delimiter at the beginning or at the end of the string is ignored.  )) **@@@@@@@ U@@1@! @@@@@@n-bounded_split( ** *+@б@гE®exp *+ *+@@ @@@3        @8@A@@б@г ڠ&string *+ *+@@ @@@@@б@г #int "*+ #*+@@ @@@ @@г $list /*+* 0*+.@г &string 9*+# :*+)@@ @@@7@@@@@@< @@@$@@ @@A'@@@8@@ @@F;@@@N@@ @@KQ#@@@ U**&@ l Same as {!Str.split}, but splits into at most [n] substrings, where [n] is the extra integer parameter.  b+/+/ c+q+@@@@@@@ {V@@6@ v@@@@@@j+split_delim) y++ z++@б@гǠ®exp ++ ++@@ @@@3        @8@A@@б@г \&string ++ ++@@ @@@@@г $list ++ ++@г s&string ++ ++@@ @@@(@@@@@@ - @@@$@@! @@"2'@@@:@@# @@$7=@@@ ++!@  5 Same as {!Str.split} but occurrences of the delimiter at the beginning and at the end of the string are recognized and returned as empty strings in the result. For instance, [split_delim (regexp " ") " abc "] returns [[""; "abc"; ""]], while [split] with the same arguments returns [["abc"]].  ++ ,-@@@@@@@ W@@1@  䐠@@@@@@V3bounded_split_delim* -- --'@б@г 5®exp --* --0@@ @@@%3        @o8@A@@б@г ʠ&string --4 --:@@ @@@&@@б@г 堐#int --> --A@@ @@@' @@г $list --L --P@г &string )--E *--K@@ @@@(7@@@@@@*< @@@$@@+ @@,A'@@@8@@- @@.F;@@@N@@/ @@0KQ#@@@ E--&@ Same as {!Str.bounded_split}, but occurrences of the delimiter at the beginning and at the end of the string are recognized and returned as empty strings in the result.  R-Q-Q S-.@@@@@@@ kX@@6@  f@@@@@@jA+,split_result+B j..  k..@@;@@$Text, B@@@1@@ y ..  z ...@@ Z@%Delim- P@@@2@@  ./.1  ./.B@@ [@@@A@@@@@ ..@@@@ Y@@#    ..$@@г!&string  ..("@@(3        @\9;@@@A@@@@@@@@@A(@@@@*@#&&  ./.3  ./.8@@г(&string  ./.<)@@/*@@@@,@@A@(@@3        @@A),@*full_split.  .D.H  .D.R@б@г ®exp  .D.U  .D.[@@ @@@<3        @0hb@A@@б@г &string  .D._  .D.e@@ @@@=@@г V$list  .D.v  .D.z@г,split_result  .D.i  .D.u@@ @@@>(@@@@@@@- @@@$@@A @@B2'@@@:@@C @@D7=@@@  .D.D!@ D 0 Same as {!Str.split_delim}, but returns the delimiters as well as the substrings contained between delimiters. The former are tagged [Delim] in the result list; the latter are tagged [Text]. For instance, [full_split (regexp "[{}]") "{ab}"] returns [[Delim "{"; Text "ab"; Delim "}"]].   .{.{ //@@@@@@@ ,\@@1@ T '@@@@@@V2bounded_full_split/ *// +//@б@г x®exp 5// 6//@@ @@@E3 7 6 6 7 7 7 7 7@o8@A@@б@г &string F// G//@@ @@@F@@б@г (#int U// V//@@ @@@G @@г Ӡ$list b// c//@г,split_result l// m//@@ @@@H7@@@@@@J< @@@$@@K @@LA'@@@8@@M @@NF;@@@N@@O @@PKQ#@@@ //&@ Ɛ Same as {!Str.bounded_split_delim}, but returns the delimiters as well as the substrings contained between delimiters. The former are tagged [Delim] in the result list; the latter are tagged [Text].  // 00@@@@@@@ ]@@6@  @@@@@@j  ; {1 Extracting substrings}  00 00@@@@@@3        @|1@A-string_before0 00 01@б@г &string 01  01@@ @@@Q@@б@г #int 01 01@@ @@@R)@@г &string 01 01 @@ @@@S6@@@@@T@@U; @@@)@@V @@W@,@@@ 00@ 6 [string_before s n] returns the substring of all characters of [s] that precede position [n] (excluding the character at position [n]).  1!1! !11@@@@@@@ ^@@"@ F @@@@@@_,string_after1 #11 #11@б@г &string '#11 (#11@@ @@@X3 ) ( ( ) ) ) ) )@xs8@A@@б@г #int 8#11 9#11@@ @@@Y@@г &string E#11 F#11@@ @@@Z@@@@@[@@\# @@@+@@] @@^(.@@@ W#11@ [string_after s n] returns the substring of all characters of [s] that follow position [n] (including the character at position [n]).  d$11 e&2`2t@@@@@@@ }_@@"@  x@@@@@@G+first_chars2 {(2v2z |(2v2@б@г M&string (2v2 (2v2@@ @@@_3        @`u8@A@@б@г j#int (2v2 (2v2@@ @@@`@@г k&string (2v2 (2v2@@ @@@a@@@@@b@@c# @@@+@@d @@e(.@@@ (2v2v@ r [first_chars s n] returns the first [n] characters of [s]. This is the same function as {!Str.string_before}.  )22 *23@@@@@@@ `@@"@  א@@@@@@G*last_chars3 ,33 ,33'@б@г &string ,33* ,330@@ @@@f3        @`u8@A@@б@г ɠ#int ,334 ,337@@ @@@g@@г ʠ&string,33;,33A@@ @@@h@@@@@i@@j# @@@+@@k @@l(.@@@,33@ S : [last_chars s n] returns the last [n] characters of [s]. "-3B3B#-3B3@@@@@@@;a@@"@ c6@@@@@@G@ z tA@ Q (@  @  @ v M@ - @  @ b @  @  /@ @@}T@4@@e@2@r@R@f@F @@l @@ @A@c@C@u@U@@^@@3nmmnnnnn@`@A@ H************************************************************************wA@@xA@L@ H }BMM~BM@ 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@ 7* Regular expressions and high-level string processing ˠ:* {1 Regular expressions}  - * The {!Str} library provides regular expressions on sequences of bytes. It is, in general, unsuitable to match Unicode characters.   ,* The type of compiled regular expressions.   * Compile a regular expression. The following constructs are recognized: - [. ] Matches any character except newline. - [* ] (postfix) Matches the preceding expression zero, one or several times - [+ ] (postfix) Matches the preceding expression one or several times - [? ] (postfix) Matches the preceding expression once or not at all - [[..] ] Character set. Ranges are denoted with [-], as in [[a-z]]. An initial [^], as in [[^0-9]], complements the set. To include a [\]] character in a set, make it the first character of the set. To include a [-] character in a set, make it the first or the last character of the set. - [^ ] Matches at beginning of line: either at the beginning of the matched string, or just after a '\n' character. - [$ ] Matches at end of line: either at the end of the matched string, or just before a '\n' character. - [\| ] (infix) Alternative between two expressions. - [\(..\)] Grouping and naming of the enclosed expression. - [\1 ] The text matched by the first [\(...\)] expression ([\2] for the second expression, and so on up to [\9]). - [\b ] Matches word boundaries. - [\ ] Quotes special characters. The special characters are [$^\.*+?[]]. In regular expressions you will often use backslash characters; it's easier to use a quoted string literal [{|...|}] to avoid having to escape backslashes. For example, the following expression: {[ let r = Str.regexp {|hello \([A-Za-z]+\)|} in Str.replace_first r {|\1|} "hello world" ]} returns the string ["world"]. If you want a regular expression that matches a literal backslash character, you need to double it: [Str.regexp {|\\|}]. You can use regular string literals ["..."] too, however you will have to escape backslashes. The example above can be rewritten with a regular string literal as: {[ let r = Str.regexp "hello \\([A-Za-z]+\\)" in Str.replace_first r "\\1" "hello world" ]} And the regular expression for matching a backslash becomes a quadruple backslash: [Str.regexp "\\\\"].  * Same as [regexp], but the compiled expression will match text in a case-insensitive way: uppercase and lowercase letters will be considered equivalent.  s V* [Str.quote s] returns a regexp string that matches exactly [s] and nothing else.  + b* [Str.regexp_string s] returns a regular expression that matches exactly [s] and nothing else. 㠠 y* [Str.regexp_string_case_fold] is similar to {!Str.regexp_string}, but the regexp matches in a case-insensitive way.  $* {1 String matching and searching}  * [string_match r s start] tests whether a substring of [s] that starts at position [start] matches the regular expression [r]. The first character of a string has position [0], as usual.   :* [search_forward r s start] searches the string [s] for a substring matching the regular expression [r]. The search starts at position [start] and proceeds towards the end of the string. Return the position of the first character of the matched substring. @raise Not_found if no substring matches.  U* [search_backward r s last] searches the string [s] for a substring matching the regular expression [r]. The search first considers substrings that start at position [last] and proceeds towards the beginning of string. Return the position of the first character of the matched substring. @raise Not_found if no substring matches.  = * Similar to {!Str.string_match}, but also returns true if the argument string is a prefix of a string that matches. This includes the case of a true complete match.  ͠ * [matched_string s] returns the substring of [s] that was matched by the last call to one of the following matching or searching functions: - {!Str.string_match} - {!Str.search_forward} - {!Str.search_backward} - {!Str.string_partial_match} - {!Str.global_substitute} - {!Str.substitute_first} provided that none of the following functions was called in between: - {!Str.global_replace} - {!Str.replace_first} - {!Str.split} - {!Str.bounded_split} - {!Str.split_delim} - {!Str.bounded_split_delim} - {!Str.full_split} - {!Str.bounded_full_split} Note: in the case of [global_substitute] and [substitute_first], a call to [matched_string] is only valid within the [subst] argument, not after [global_substitute] or [substitute_first] returns. The user must make sure that the parameter [s] is the same string that was passed to the matching or searching function.  * [match_beginning()] returns the position of the first character of the substring that was matched by the last call to a matching or searching function (see {!Str.matched_string} for details).  = * [match_end()] returns the position of the character following the last character of the substring that was matched by the last call to a matching or searching function (see {!Str.matched_string} for details).  * [matched_group n s] returns the substring of [s] that was matched by the [n]th group [\(...\)] of the regular expression that was matched by the last call to a matching or searching function (see {!Str.matched_string} for details). When [n] is [0], it returns the substring matched by the whole regular expression. The user must make sure that the parameter [s] is the same string that was passed to the matching or searching function. @raise Not_found if the [n]th group of the regular expression was not matched. This can happen with groups inside alternatives [\|], options [?] or repetitions [*]. For instance, the empty string will match [\(a\)*], but [matched_group 1 ""] will raise [Not_found] because the first group itself was not matched.  * [group_beginning n] returns the position of the first character of the substring that was matched by the [n]th group of the regular expression that was matched by the last call to a matching or searching function (see {!Str.matched_string} for details). @raise Not_found if the [n]th group of the regular expression was not matched. @raise Invalid_argument if there are fewer than [n] groups in the regular expression. Q * [group_end n] returns the position of the character following the last character of substring that was matched by the [n]th group of the regular expression that was matched by the last call to a matching or searching function (see {!Str.matched_string} for details). @raise Not_found if the [n]th group of the regular expression was not matched. @raise Invalid_argument if there are fewer than [n] groups in the regular expression.  2* {1 Replacement}  * [global_replace regexp templ s] returns a string identical to [s], except that all substrings of [s] that match [regexp] have been replaced by [templ]. The replacement template [templ] can contain [\1], [\2], etc; these sequences will be replaced by the text matched by the corresponding group in the regular expression. [\0] stands for the text matched by the whole regular expression.  v* Same as {!Str.global_replace}, except that only the first substring matching the regular expression is replaced.  0* [global_substitute regexp subst s] returns a string identical to [s], except that all substrings of [s] that match [regexp] have been replaced by the result of function [subst]. The function [subst] is called once for each matching substring, and receives [s] (the whole text) as argument.  y* Same as {!Str.global_substitute}, except that only the first substring matching the regular expression is replaced.  * [replace_matched repl s] returns the replacement text [repl] in which [\1], [\2], etc. have been replaced by the text matched by the corresponding groups in the regular expression that was matched by the last call to a matching or searching function (see {!Str.matched_string} for details). [s] must be the same string that was passed to the matching or searching function. 0* {1 Splitting}  8* [split r s] splits [s] into substrings, taking as delimiters the substrings that match [r], and returns the list of substrings. For instance, [split (regexp "[ \t]+") s] splits [s] into blank-separated words. An occurrence of the delimiter at the beginning or at the end of the string is ignored. < m* Same as {!Str.split}, but splits into at most [n] substrings, where [n] is the extra integer parameter.  6* Same as {!Str.split} but occurrences of the delimiter at the beginning and at the end of the string are recognized and returned as empty strings in the result. For instance, [split_delim (regexp " ") " abc "] returns [[""; "abc"; ""]], while [split] with the same arguments returns [["abc"]]. R * Same as {!Str.bounded_split}, but occurrences of the delimiter at the beginning and at the end of the string are recognized and returned as empty strings in the result. Ӡ 1* Same as {!Str.split_delim}, but returns the delimiters as well as the substrings contained between delimiters. The former are tagged [Delim] in the result list; the latter are tagged [Text]. For instance, [full_split (regexp "[{}]") "{ab}"] returns [[Delim "{"; Text "ab"; Delim "}"]].  * Same as {!Str.bounded_split_delim}, but returns the delimiters as well as the substrings contained between delimiters. The former are tagged [Delim] in the result list; the latter are tagged [Text]. <* {1 Extracting substrings} { * [string_before s n] returns the substring of all characters of [s] that precede position [n] (excluding the character at position [n]). , * [string_after s n] returns the substring of all characters of [s] that follow position [n] (including the character at position [n]). Р s* [first_chars s n] returns the first [n] characters of [s]. This is the same function as {!Str.string_before}. t ;* [last_chars s n] returns the last [n] characters of [s]. @?,../../ocamlc)-nostdlib"-I,../../stdlib"-c(-absname"-w5+a-4-9-41-42-44-45-48+-warn-error"+A*-bin-annot"-g0-strict-sequence/-strict-formatsGH G/builds/workspace/main/flambda/false/label/ocaml-linux-32/otherlibs/str @@0=N4F-; 3MLLMMMMM@K@@8CamlinternalFormatBasics0|.e1R$|o&Stdlib0t0VoS%{<F:s0݅-d6B2@0݅-d6B2Ab@ M  X@t@g@Hj@@  T @  @@c@@ S  ; @̐ @j@@ ΐ 2@  N Ґ @@  [@Ѱ  @j@< u@@ 7@8@@̐+@@@@  ְ  #@  @@P@@