123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656open!Import(** Interface for Unicode encodings, such as UTF-8. Written with an abstract type, and
specialized below. *)moduletypeUtf=sigtypet[@@deriving_inlinesexp_grammar]valt_sexp_grammar:tSexplib0.Sexp_grammar.t[@@@end](** [t_of_sexp] and [of_string] will raise if the input is invalid in this encoding. See
[sanitize] below to construct a valid [t] from arbitrary input. *)includeIdentifiable.Swithtypet:=t(** Interpret [t] as a container of Unicode scalar values, rather than of ASCII
characters. Indexes, length, etc. are with respect to [Uchar.t]. *)includeIndexed_container.S0_with_creatorswithtypet:=tandtypeelt=Uchar0.t(** Produce a sequence of unicode characters. *)valto_sequence:t->Uchar0.tSequence.t(** Reports whether a string is valid in this encoding. *)valis_valid:string->bool(** Create a [t] from a string by replacing any byte sequences that are invalid in this
encoding with [Uchar.replacement_char]. This can be used to decode strings that may
be encoded incorrectly. *)valsanitize:string->t(** Decodes the Unicode scalar value at the given byte index in this encoding. Raises if
[byte_pos] does not refer to the start of a Unicode scalar value. *)valget:t->byte_pos:int->Uchar0.t(** Creates a [t] without sanitizing or validating the string. Other functions in this
interface may raise or produce unpredictable results if the string is invalid in
this encoding. *)valof_string_unchecked:string->t(** Similar to [String.split], but splits on a [Uchar.t] in [t]. If you want to split on
a [char], first convert it with [Uchar.of_char], but note that the actual byte(s) on
which [t] is split may not be the same as the [char] byte depending on both [char]
and the encoding of [t]. For example, splitting on 'α' in UTF-8 or on '\n' in UTF-16
is actually splitting on a 2-byte sequence. *)valsplit:t->on:Uchar0.t->tlist(** The name of this encoding scheme; e.g., "UTF-8". *)valcodec_name:string(** Counts the number of unicode scalar values in [t].
This function is not a good proxy for display width, as some scalar values have
display widths > 1. Many native applications such as terminal emulators use
[wcwidth] (see [man 3 wcwidth]) to compute the display width of a scalar value. See
the uucp library's [Uucp.Break.tty_width_hint] for an implementation of [wcwidth]'s
logic. However, this is merely best-effort, as display widths will vary based on the
font and underlying text shaping engine (see docs on [tty_width_hint] for details).
For applications that support Grapheme clusters (many terminal emulators do not),
[t] should first be split into Grapheme clusters and then the display width of each
of those Grapheme clusters needs to be computed (which is the max display width of
the scalars that are in the cluster).
There are some active efforts to improve the current state of affairs:
- https://github.com/wez/wezterm/issues/4320
- https://www.unicode.org/L2/L2023/23194-text-terminal-wg-report.pdf *)vallength_in_uchars:t->int(** [length] could be misinterpreted as counting bytes. We direct users to other,
clearer options. *)vallength:t->int[@@alertlength_in_uchars"Use [length_in_uchars] to count unicode scalar values or [String.length] to \
count bytes"]end(** Iterface for Unicode encodings, specialized for string representation. *)moduletypeUtf_as_string=Utfwithtypet=privatestringmoduletypeString=sig(** An extension of the standard [StringLabels]. If you [open Base], you'll get these
extensions in the [String] module. *)open!Importtypet=string[@@deriving_inlineglobalize,sexp,sexp_grammar]valglobalize:t->tincludeSexplib0.Sexpable.Swithtypet:=tvalt_sexp_grammar:tSexplib0.Sexp_grammar.t[@@@end]valsub:(t,t)Blit.sub(** [sub] with no bounds checking, and always returns a new copy *)valunsafe_sub:t->pos:int->len:int->tvalsubo:(t,t)Blit.suboincludeIndexed_container.S0_with_creatorswithtypet:=twithtypeelt=charincludeIdentifiable.Swithtypet:=tincludePpx_compare_lib.Comparable.S_localwithtypet:=tincludeInvariant.Swithtypet:=t(** Maximum length of a string. *)valmax_length:intvalmem:t->char->boolexternallength:(t[@local_opt])->int="%string_length"externalget:(t[@local_opt])->(int[@local_opt])->char="%string_safe_get"(** [unsafe_get t i] is like [get t i] but does not perform bounds checking. The caller
must ensure that it is a memory-safe operation. *)externalunsafe_get:(string[@local_opt])->(int[@local_opt])->char="%string_unsafe_get"valmake:int->char->t(** String append. Also available unqualified, but re-exported here for documentation
purposes.
Note that [a ^ b] must copy both [a] and [b] into a newly-allocated result string, so
[a ^ b ^ c ^ ... ^ z] is quadratic in the number of strings. [String.concat] does not
have this problem -- it allocates the result buffer only once. *)val(^):t->t->t(** Concatenates all strings in the list using separator [sep] (with a default separator
[""]). *)valconcat:?sep:t->tlist->t(** Special characters are represented by escape sequences, following the lexical
conventions of OCaml. *)valescaped:t->tvalcontains:?pos:int->?len:int->t->char->bool(** Operates on the whole string using the US-ASCII character set,
e.g. [uppercase "foo" = "FOO"]. *)valuppercase:t->tvallowercase:t->t(** Operates on just the first character using the US-ASCII character set,
e.g. [capitalize "foo" = "Foo"]. *)valcapitalize:t->tvaluncapitalize:t->t(** [Caseless] compares and hashes strings ignoring case, so that for example
[Caseless.equal "OCaml" "ocaml"] and [Caseless.("apple" < "Banana")] are [true].
[Caseless] also provides case-insensitive [is_suffix] and [is_prefix] functions, so
that for example [Caseless.is_suffix "OCaml" ~suffix:"AmL"] and [Caseless.is_prefix
"OCaml" ~prefix:"oc"] are [true]. *)moduleCaseless:sigtypenonrect=t[@@deriving_inlinehash,sexp,sexp_grammar]includePpx_hash_lib.Hashable.Swithtypet:=tincludeSexplib0.Sexpable.Swithtypet:=tvalt_sexp_grammar:tSexplib0.Sexp_grammar.t[@@@end]includeComparable.Swithtypet:=tincludePpx_compare_lib.Comparable.S_localwithtypet:=tvalis_suffix:t->suffix:t->boolvalis_prefix:t->prefix:t->boolvalis_substring:t->substring:t->boolvalis_substring_at:t->pos:int->substring:t->boolvalsubstr_index:?pos:int->t->pattern:t->intoptionvalsubstr_index_exn:?pos:int->t->pattern:t->intvalsubstr_index_all:t->may_overlap:bool->pattern:t->intlistvalsubstr_replace_first:?pos:int->t->pattern:t->with_:t->tvalsubstr_replace_all:t->pattern:t->with_:t->tend(** [index] gives the index of the first appearance of [char] in the string when
searching from left to right, or [None] if it's not found. [rindex] does the same but
searches from the right.
For example, [String.index "Foo" 'o'] is [Some 1] while [String.rindex "Foo" 'o'] is
[Some 2].
The [_exn] versions return the actual index (instead of an option) when [char] is
found, and raise [Stdlib.Not_found] or [Not_found_s] otherwise.
*)valindex:t->char->intoptionvalindex_exn:t->char->intvalindex_from:t->int->char->intoptionvalindex_from_exn:t->int->char->intvalrindex:t->char->intoptionvalrindex_exn:t->char->intvalrindex_from:t->int->char->intoptionvalrindex_from_exn:t->int->char->int(** Produce a sequence of the characters in a string. *)valto_sequence:t->charSequence.t(** Read the characters in a full sequence and produce a string. *)valof_sequence:charSequence.t->t(** Substring search and replace functions. They use the Knuth-Morris-Pratt algorithm
(KMP) under the hood.
The functions in the [Search_pattern] module allow the program to preprocess the
searched pattern once and then use it many times without further allocations. *)moduleSearch_pattern:sigtypet[@@deriving_inlinesexp_of]valsexp_of_t:t->Sexplib0.Sexp.t[@@@end](** [create pattern] preprocesses [pattern] as per KMP, building an [int array] of
length [length pattern]. All inputs are valid. *)valcreate:?case_sensitive:bool(** default = true *)->string->t(** [pattern t] returns the string pattern used to create [t]. *)valpattern:t->string(** [case_sensitive t] returns whether [t] matches strings case-sensitively. *)valcase_sensitive:t->bool(** [matches pat str] returns true if [str] matches [pat] *)valmatches:t->string->bool(** [pos < 0] or [pos >= length string] result in no match (hence [index] returns
[None] and [index_exn] raises). *)valindex:?pos:int->t->in_:string->intoptionvalindex_exn:?pos:int->t->in_:string->int(** [may_overlap] determines whether after a successful match, [index_all] should start
looking for another one at the very next position ([~may_overlap:true]), or jump to
the end of that match and continue from there ([~may_overlap:false]), e.g.:
- [index_all (create "aaa") ~may_overlap:false ~in_:"aaaaBaaaaaa" = [0; 5; 8]]
- [index_all (create "aaa") ~may_overlap:true ~in_:"aaaaBaaaaaa" = [0; 1; 5; 6; 7;
8]]
E.g., [replace_all] internally calls [index_all ~may_overlap:false]. *)valindex_all:t->may_overlap:bool->in_:string->intlist(** Note that the result of [replace_all pattern ~in_:text ~with_:r] may still
contain [pattern], e.g.,
{[
replace_all (create "bc") ~in_:"aabbcc" ~with_:"cb" = "aabcbc"
]} *)valreplace_first:?pos:int->t->in_:string->with_:string->stringvalreplace_all:t->in_:string->with_:string->string(** Similar to [String.split] or [String.split_on_chars], but instead uses a given
search pattern as the separator. Separators are non-overlapping. *)valsplit_on:t->string->stringlist(**/**)(*_ See the Jane Street Style Guide for an explanation of [Private] submodules:
https://opensource.janestreet.com/standards/#private-submodules *)modulePrivate:sigtypepublic=ttypet={pattern:string;case_sensitive:bool;kmp_array:intarray}[@@deriving_inlineequal~localize,sexp_of]includePpx_compare_lib.Equal.Swithtypet:=tincludePpx_compare_lib.Equal.S_localwithtypet:=tvalsexp_of_t:t->Sexplib0.Sexp.t[@@@end]valrepresentation:public->tendend(** Substring search and replace convenience functions. They call [Search_pattern.create]
and then forget the preprocessed pattern when the search is complete. [pos < 0] or
[pos >= length t] result in no match (hence [substr_index] returns [None] and
[substr_index_exn] raises). [may_overlap] indicates whether to report overlapping
matches, see [Search_pattern.index_all]. *)valsubstr_index:?pos:int->t->pattern:t->intoptionvalsubstr_index_exn:?pos:int->t->pattern:t->intvalsubstr_index_all:t->may_overlap:bool->pattern:t->intlistvalsubstr_replace_first:?pos:int->t->pattern:t->with_:t->t(** As with [Search_pattern.replace_all], the result may still contain [pattern]. *)valsubstr_replace_all:t->pattern:t->with_:t->t(** [is_substring ~substring:"bar" "foo bar baz"] is true. *)valis_substring:t->substring:t->bool(** [is_substring_at "foo bar baz" ~pos:4 ~substring:"bar"] is true. *)valis_substring_at:t->pos:int->substring:t->bool(** Returns the reversed list of characters contained in a list. *)valto_list_rev:t->charlist(** [rev t] returns [t] in reverse order. *)valrev:t->t(** [is_suffix s ~suffix] returns [true] if [s] ends with [suffix]. *)valis_suffix:t->suffix:t->bool(** [is_prefix s ~prefix] returns [true] if [s] starts with [prefix]. *)valis_prefix:t->prefix:t->bool(** If the string [s] contains the character [on], then [lsplit2_exn s ~on] returns a pair
containing [s] split around the first appearance of [on] (from the left). Raises
[Stdlib.Not_found] or [Not_found_s] when [on] cannot be found in [s]. *)vallsplit2_exn:t->on:char->t*t(** If the string [s] contains the character [on], then [rsplit2_exn s ~on] returns a pair
containing [s] split around the first appearance of [on] (from the right). Raises
[Stdlib.Not_found] or [Not_found_s] when [on] cannot be found in [s]. *)valrsplit2_exn:t->on:char->t*t(** [lsplit2 s ~on] optionally returns [s] split into two strings around the
first appearance of [on] from the left. *)vallsplit2:t->on:char->(t*t)option(** [rsplit2 s ~on] optionally returns [s] split into two strings around the first
appearance of [on] from the right. *)valrsplit2:t->on:char->(t*t)option(** [split s ~on] returns a list of substrings of [s] that are separated by [on].
Consecutive [on] characters will cause multiple empty strings in the result.
Splitting the empty string returns a list of the empty string, not the empty list. *)valsplit:t->on:char->tlist(** [split_on_chars s ~on] returns a list of all substrings of [s] that are separated by
one of the chars from [on]. [on] are not grouped. So a grouping of [on] in the
source string will produce multiple empty string splits in the result. *)valsplit_on_chars:t->on:charlist->tlist(** [split_lines t] returns the list of lines that comprise [t]. The lines do not include
the trailing ["\n"] or ["\r\n"]. *)valsplit_lines:t->tlist(** [lfindi ?pos t ~f] returns the smallest [i >= pos] such that [f i t.[i]], if there is
such an [i]. By default, [pos = 0]. *)vallfindi:?pos:int->t->f:(int->char->bool)->intoption(** [rfindi ?pos t ~f] returns the largest [i <= pos] such that [f i t.[i]], if there is
such an [i]. By default [pos = length t - 1]. *)valrfindi:?pos:int->t->f:(int->char->bool)->intoption(** [lstrip ?drop s] returns a string with consecutive chars satisfying [drop] (by default
white space, e.g. tabs, spaces, newlines, and carriage returns) stripped from the
beginning of [s]. *)vallstrip:?drop:(char->bool)->t->t(** [rstrip ?drop s] returns a string with consecutive chars satisfying [drop] (by default
white space, e.g. tabs, spaces, newlines, and carriage returns) stripped from the end
of [s]. *)valrstrip:?drop:(char->bool)->t->t(** [strip ?drop s] returns a string with consecutive chars satisfying [drop] (by default
white space, e.g. tabs, spaces, newlines, and carriage returns) stripped from the
beginning and end of [s]. *)valstrip:?drop:(char->bool)->t->t(** Like [map], but allows the replacement of a single character with zero or two or more
characters. *)valconcat_map:?sep:t->t->f:(char->t)->tvalconcat_mapi:?sep:t->t->f:(int->char->t)->t(** [tr ~target ~replacement s] replaces every instance of [target] in [s] with
[replacement]. *)valtr:target:char->replacement:char->t->t(** [tr_multi ~target ~replacement] returns a function that replaces every
instance of a character in [target] with the corresponding character in
[replacement].
If [replacement] is shorter than [target], it is lengthened by repeating
its last character. Empty [replacement] is illegal unless [target] also is.
If [target] contains multiple copies of the same character, the last
corresponding [replacement] character is used. Note that character ranges
are {b not} supported, so [~target:"a-z"] means the literal characters ['a'],
['-'], and ['z']. *)valtr_multi:target:t->replacement:t->(t->t)Staged.t(** [chop_suffix_exn s ~suffix] returns [s] without the trailing [suffix],
raising [Invalid_argument] if [suffix] is not a suffix of [s]. *)valchop_suffix_exn:t->suffix:t->t(** [chop_prefix_exn s ~prefix] returns [s] without the leading [prefix],
raising [Invalid_argument] if [prefix] is not a prefix of [s]. *)valchop_prefix_exn:t->prefix:t->tvalchop_suffix:t->suffix:t->toptionvalchop_prefix:t->prefix:t->toption(** [chop_suffix_if_exists s ~suffix] returns [s] without the trailing [suffix], or just
[s] if [suffix] isn't a suffix of [s].
Equivalent to [chop_suffix s ~suffix |> Option.value ~default:s], but avoids
allocating the intermediate option. *)valchop_suffix_if_exists:t->suffix:t->t(** [chop_prefix_if_exists s ~prefix] returns [s] without the leading [prefix], or just
[s] if [prefix] isn't a prefix of [s].
Equivalent to [chop_prefix s ~prefix |> Option.value ~default:s], but avoids
allocating the intermediate option. *)valchop_prefix_if_exists:t->prefix:t->t(** [suffix s n] returns the longest suffix of [s] of length less than or equal to [n]. *)valsuffix:t->int->t(** [prefix s n] returns the longest prefix of [s] of length less than or equal to [n]. *)valprefix:t->int->t(** [drop_suffix s n] drops the longest suffix of [s] of length less than or equal to
[n]. *)valdrop_suffix:t->int->t(** [drop_prefix s n] drops the longest prefix of [s] of length less than or equal to
[n]. *)valdrop_prefix:t->int->t(** Produces the longest common suffix, or [""] if the list is empty. *)valcommon_suffix:tlist->t(** Produces the longest common prefix, or [""] if the list is empty. *)valcommon_prefix:tlist->t(** Produces the length of the longest common suffix, or 0 if the list is empty. *)valcommon_suffix_length:tlist->int(** Produces the length of the longest common prefix, or 0 if the list is empty. *)valcommon_prefix_length:tlist->int(** Produces the longest common suffix. *)valcommon_suffix2:t->t->t(** Produces the longest common prefix. *)valcommon_prefix2:t->t->t(** Produces the length of the longest common suffix. *)valcommon_suffix2_length:t->t->int(** Produces the length of the longest common prefix. *)valcommon_prefix2_length:t->t->int(** [concat_array sep ar] like {!String.concat}, but operates on arrays. *)valconcat_array:?sep:t->tarray->t(** Builds a multiline text from a list of lines. Each line is terminated and then
concatenated. Equivalent to:
{[
String.concat (List.map lines ~f:(fun line ->
line ^ if crlf then "\r\n" else "\n"))
]}
*)valconcat_lines:?crlf:bool(** default [false] *)->stringlist->string(** Slightly faster hash function on strings. *)externalhash:t->int="Base_hash_string"[@@noalloc](** Fast equality function on strings, doesn't use [compare_val]. *)valequal:t->t->boolvalequal__local:t->t->boolvalof_char:char->tvalof_char_list:charlist->t(** [pad_left ?char s ~len] returns [s] padded to the length [len] by adding characters
[char] to the beginning of the string. If s is already longer than [len] it is
returned unchanged. *)valpad_left:?char:char(** default is [' '] *)->string->len:int->string(** [pad_right ?char ~s len] returns [s] padded to the length [len] by adding characters
[char] to the end of the string. If s is already longer than [len] it is returned
unchanged. *)valpad_right:?char:char(** default is [' '] *)->string->len:int->string(** Reports the Levenshtein edit distance between two strings. Computes the minimum number
of single-character insertions, deletions, and substitutions needed to transform one
into the other.
For strings of length M and N, its time complexity is O(M*N) and its space complexity
is O(min(M,N)). *)valedit_distance:string->string->int(** Operations for escaping and unescaping strings, with parameterized escape and
escapeworthy characters. Escaping/unescaping using this module is more efficient than
using Pcre. Benchmark code can be found in core/benchmarks/string_escaping.ml. *)moduleEscaping:sig(** [escape_gen_exn escapeworthy_map escape_char] returns a function that will escape a
string [s] as follows: if [(c1,c2)] is in [escapeworthy_map], then all occurrences
of [c1] are replaced by [escape_char] concatenated to [c2].
Raises an exception if [escapeworthy_map] is not one-to-one. If [escape_char] is
not in [escapeworthy_map], then it will be escaped to itself.*)valescape_gen_exn:escapeworthy_map:(char*char)list->escape_char:char->(string->string)Staged.tvalescape_gen:escapeworthy_map:(char*char)list->escape_char:char->(string->string)Or_error.t(** [escape ~escapeworthy ~escape_char s] is
{[
escape_gen_exn ~escapeworthy_map:(List.zip_exn escapeworthy escapeworthy)
~escape_char
]}
Duplicates and [escape_char] will be removed from [escapeworthy]. So, no
exception will be raised *)valescape:escapeworthy:charlist->escape_char:char->(string->string)Staged.t(** [unescape_gen_exn] is the inverse operation of [escape_gen_exn]. That is,
{[
let escape = Staged.unstage (escape_gen_exn ~escapeworthy_map ~escape_char) in
let unescape = Staged.unstage (unescape_gen_exn ~escapeworthy_map ~escape_char) in
assert (s = unescape (escape s))
]}
always succeed when ~escapeworthy_map is not causing exceptions. *)valunescape_gen_exn:escapeworthy_map:(char*char)list->escape_char:char->(string->string)Staged.tvalunescape_gen:escapeworthy_map:(char*char)list->escape_char:char->(string->string)Or_error.t(** [unescape ~escape_char] is defined as [unescape_gen_exn ~map:\[\] ~escape_char] *)valunescape:escape_char:char->(string->string)Staged.t(** Any char in an escaped string is either escaping, escaped, or literal. For example,
for escaped string ["0_a0__0"] with [escape_char] as ['_'], pos 1 and 4 are
escaping, 2 and 5 are escaped, and the rest are literal.
[is_char_escaping s ~escape_char pos] returns true if the char at [pos] is escaping,
false otherwise. *)valis_char_escaping:string->escape_char:char->int->bool(** [is_char_escaped s ~escape_char pos] returns true if the char at [pos] is escaped,
false otherwise. *)valis_char_escaped:string->escape_char:char->int->bool(** [is_char_literal s ~escape_char pos] returns true if the char at [pos] is not
escaped or escaping. *)valis_char_literal:string->escape_char:char->int->bool(** [index s ~escape_char char] finds the first literal (not escaped) instance of [char]
in s starting from 0. *)valindex:string->escape_char:char->char->intoptionvalindex_exn:string->escape_char:char->char->int(** [rindex s ~escape_char char] finds the first literal (not escaped) instance of
[char] in [s] starting from the end of [s] and proceeding towards 0. *)valrindex:string->escape_char:char->char->intoptionvalrindex_exn:string->escape_char:char->char->int(** [index_from s ~escape_char pos char] finds the first literal (not escaped) instance
of [char] in [s] starting from [pos] and proceeding towards the end of [s]. *)valindex_from:string->escape_char:char->int->char->intoptionvalindex_from_exn:string->escape_char:char->int->char->int(** [rindex_from s ~escape_char pos char] finds the first literal (not escaped)
instance of [char] in [s] starting from [pos] and towards 0. *)valrindex_from:string->escape_char:char->int->char->intoptionvalrindex_from_exn:string->escape_char:char->int->char->int(** [split s ~escape_char ~on] returns a list of substrings of [s] that are separated by
literal versions of [on]. Consecutive [on] characters will cause multiple empty
strings in the result. Splitting the empty string returns a list of the empty
string, not the empty list.
E.g., [split ~escape_char:'_' ~on:',' "foo,bar_,baz" = ["foo"; "bar_,baz"]]. *)valsplit:string->on:char->escape_char:char->stringlist(** [split_on_chars s ~on] returns a list of all substrings of [s] that are separated by
one of the literal chars from [on]. [on] are not grouped. So a grouping of [on] in
the source string will produce multiple empty string splits in the result.
E.g., [split_on_chars ~escape_char:'_' ~on:[',';'|'] "foo_|bar,baz|0" ->
["foo_|bar"; "baz"; "0"]]. *)valsplit_on_chars:string->on:charlist->escape_char:char->stringlist(** [lsplit2 s ~on ~escape_char] splits s into a pair on the first literal instance of
[on] (meaning the first unescaped instance) starting from the left. *)vallsplit2:string->on:char->escape_char:char->(string*string)optionvallsplit2_exn:string->on:char->escape_char:char->string*string(** [rsplit2 s ~on ~escape_char] splits [s] into a pair on the first literal
instance of [on] (meaning the first unescaped instance) starting from the
right. *)valrsplit2:string->on:char->escape_char:char->(string*string)optionvalrsplit2_exn:string->on:char->escape_char:char->string*string(** These are the same as [lstrip], [rstrip], and [strip] for generic strings, except
that they only drop literal characters -- they do not drop characters that are
escaping or escaped. This makes sense if you're trying to get rid of junk
whitespace (for example), because escaped whitespace seems more likely to be
deliberate and not junk. *)vallstrip_literal:?drop:(char->bool)->t->escape_char:char->tvalrstrip_literal:?drop:(char->bool)->t->escape_char:char->tvalstrip_literal:?drop:(char->bool)->t->escape_char:char->tend(** UTF-8 encoding. See [Utf] interface. *)moduleUtf8:Utf_as_string(** UTF-16 little-endian encoding. See [Utf] interface. *)moduleUtf16le:Utf_as_string(** UTF-16 big-endian encoding. See [Utf] interface. *)moduleUtf16be:Utf_as_string(** UTF-32 little-endian encoding. See [Utf] interface. *)moduleUtf32le:Utf_as_string(** UTF-32 big-endian encoding. See [Utf] interface. *)moduleUtf32be:Utf_as_stringmoduletypeUtf=UtfmoduletypeUtf_as_string=Utf_as_stringend