This commit is contained in:
JPR 2020-07-30 11:53:59 +02:00 committed by Simon Cruanes
parent 61a8cc58bd
commit b3e32c587f

View file

@ -13,10 +13,12 @@ include module type of struct include StringLabels end
(** {{: https://caml.inria.fr/pub/docs/manual-ocaml/libref/StringLabels.html} Documentation for the standard StringLabels module} *)
val length : t -> int
(** Return the length (number of characters) of the given string. *)
(** [length s] returns the length (number of characters) of the given string [s]. *)
val blit : src:t -> src_pos:int -> dst:Bytes.t -> dst_pos:int -> len:int -> unit
(** Like {!String.blit}.
(** [blit ~src ~src_pos ~dst ~dst_pos ~len] copies [len] characters from string [src] starting at character indice [src_pos],
to the Bytes sequence [dst] starting at character indice [dst_pos].
Like {!String.blit}.
Compatible with the [-safe-string] option.
@raise Invalid_argument if indices are not valid. *)
@ -29,54 +31,56 @@ val blit_immut : t -> int -> t -> int -> int -> string
*)
val fold : f:('a -> char -> 'a) -> init:'a -> t -> 'a
(** Fold on chars by increasing index.
(** [fold ~f ~init s] folds on chars by increasing index. Computes [f((f (f init s.[0]) s.[1])) s.[n-1]].
@since 0.7 *)
(** {2 Conversions} *)
val to_gen : t -> char gen
(** Return the [gen] of characters contained in the string. *)
(** [to_gen s] returns the [gen] of characters contained in the string [s]. *)
val to_iter : t -> char iter
(** Return the [iter] of characters contained in the string.
(** [to_iter s] returns the [iter] of characters contained in the string [s].
@since 2.8 *)
val to_seq : t -> char Seq.t
(** [to_seq s] returns a [Seq.t] of the bytes in [s].
(** [to_seq s] returns the [Seq.t] of characters contained in the string [s].
Renamed from [to std_seq] since 3.0.
@since 3.0
*)
@since 3.0 *)
val to_list : t -> char list
(** Return the list of characters contained in the string. *)
(** [to_list s] returns the [list] of characters contained in the string [s]. *)
val pp_buf : Buffer.t -> t -> unit
(** Renamed from [pp] since 2.0. *)
(** [pp_buf buf s] prints [s] to the buffer [buf].
Renamed from [pp] since 2.0. *)
val pp : Format.formatter -> t -> unit
(** Print the string within quotes.
(** [pp f s] prints the string [s] within quotes to the formatter [f].
Renamed from [print] since 2.0. *)
(** {2 Strings} *)
val equal : string -> string -> bool
(** Equality function on strings. *)
(** [equal s1 s2] returns [true] iff the strings [s1] and [s2] are equal. *)
val compare : string -> string -> int
(** [compare s1 s2] compares the strings [s1] and [s2] and returns an integer that indicates
their relative position in the sort order. *)
val is_empty : string -> bool
(** [is_empty s] returns [true] iff [s] is empty (i.e. its length is 0).
@since 1.5 *)
val hash : string -> int
(** [hash s] returns the hash value of [s]. *)
val rev : string -> string
(** [rev s] returns the reverse of [s].
@since 0.17 *)
val pad : ?side:[`Left|`Right] -> ?c:char -> int -> string -> string
(** [pad n str] ensures that [str] is at least [n] bytes long,
(** [pad ?side ?c n s] ensures that the string [s] is at least [n] bytes long,
and pads it on the [side] with [c] if it's not the case.
@param side determines where padding occurs (default: [`Left]).
@param c the char used to pad (default: ' ').
@ -87,52 +91,53 @@ val of_char : char -> string
@since 0.19 *)
val of_gen : char gen -> string
(** Convert a [gen] of characters to a string. *)
(** [of_gen gen] converts a [gen] of characters to a string. *)
val of_iter : char iter -> string
(** Convert a [iter] of characters to a string.
(** [of_iter iter] converts an [iter] of characters to a string.
@since 2.8 *)
val of_seq : char Seq.t -> string
(** Convert a [sequence] of characters to a string.
(** [of_seq seq] converts a [seq] of characters to a string.
Renamed from [of_std_seq] since 3.0.
@since 3.0 *)
val of_list : char list -> string
(** Convert a list of characters to a string. *)
(** [of_list lc] converts a list of characters [lc] to a string. *)
val of_array : char array -> string
(** Convert an array of characters to a string. *)
(** [of_array ac] converts an array of characters [ac] to a string. *)
val to_array : string -> char array
(** Return the array of characters contained in the string. *)
(** [to_array s] returns the array of characters contained in the string [s]. *)
val find : ?start:int -> sub:(string [@keep_label]) -> string -> int
(** Find [sub] in string, returns its first index or [-1]. *)
(** [find ?start ~sub s] returns the starting index of the first occurrence of [sub] within [s] or [-1].
@param start starting position in [s]. *)
val find_all : ?start:int -> sub:(string [@keep_label]) -> string -> int gen
(** [find_all ~sub s] finds all occurrences of [sub] in [s], even overlapping
instances.
(** [find_all ?start ~sub s] finds all occurrences of [sub] in [s], even overlapping instances
and returns them in a generator [gen].
@param start starting position in [s].
@since 0.17 *)
val find_all_l : ?start:int -> sub:(string [@keep_label]) -> string -> int list
(** [find_all_l ~sub s] finds all occurrences of [sub] in [s] and returns
them in a list.
(** [find_all_l ?start ~sub s] finds all occurrences of [sub] in [s]
and returns them in a list.
@param start starting position in [s].
@since 0.17 *)
val mem : ?start:int -> sub:(string [@keep_label]) -> string -> bool
(** [mem ~sub s] is [true] iff [sub] is a substring of [s].
(** [mem ?start ~sub s] is [true] iff [sub] is a substring of [s].
@since 0.12 *)
val rfind : sub:(string [@keep_label]) -> string -> int
(** Find [sub] in string from the right, returns its first index or [-1].
(** [rfind ~sub s] finds [sub] in string [s] from the right, returns its first index or [-1].
Should only be used with very small [sub].
@since 0.12 *)
val replace : ?which:[`Left|`Right|`All] -> sub:(string [@keep_label]) -> by:(string [@keep_label]) -> string -> string
(** [replace ~sub ~by s] replaces some occurrences of [sub] by [by] in [s].
(** [replace ?which ~sub ~by s] replaces some occurrences of [sub] by [by] in [s].
@param which decides whether the occurrences to replace are:
{ul
{- [`Left] first occurrence from the left (beginning).}
@ -143,12 +148,12 @@ val replace : ?which:[`Left|`Right|`All] -> sub:(string [@keep_label]) -> by:(st
@since 0.14 *)
val is_sub : sub:(string [@keep_label]) -> sub_pos:int -> string -> pos:int -> sub_len:(int [@keep_label]) -> bool
(** [is_sub ~sub i s j ~len] returns [true] iff the substring of
[sub] starting at position [i] and of length [len] is a substring
of [s] starting at position [j]. *)
(** [is_sub ~sub ~sub_pos s ~pos ~sub_len] returns [true] iff the substring of [sub]
starting at position [sub_pos] and of length [sub_len] is a substring of [s]
starting at position [pos]. *)
val repeat : string -> int -> string
(** The same string, repeated n times. *)
(** [repeat s n] creates a string by repeating the string [s] [n] times. *)
val prefix : pre:(string [@keep_label]) -> string -> bool
(** [prefix ~pre s] returns [true] iff [pre] is a prefix of [s]. *)
@ -176,7 +181,7 @@ val drop : int -> string -> string
@since 0.17 *)
val take_drop : int -> string -> string * string
(** [take_drop n s = take n s, drop n s].
(** [take_drop n s] is [take n s, drop n s].
@since 0.17 *)
val lines : string -> string list
@ -184,19 +189,19 @@ val lines : string -> string list
@since 0.10 *)
val lines_gen : string -> string gen
(** [lines_gen s] returns a generator of the lines of [s] (splits along '\n').
(** [lines_gen s] returns a generator [gen] of the lines of [s] (splits along '\n').
@since 0.10 *)
val concat_gen : sep:(string [@keep_label]) -> string gen -> string
(** [concat_gen ~sep g] concatenates all strings of [g], separated with [sep].
(** [concat_gen ~sep gen] concatenates all strings of [gen], separated with [sep].
@since 0.10 *)
val unlines : string list -> string
(** [unlines l] concatenates all strings of [l], separated with '\n'.
(** [unlines ls] concatenates all strings of [ls], separated with '\n'.
@since 0.10 *)
val unlines_gen : string gen -> string
(** [unlines_gen g] concatenates all strings of [g], separated with '\n'.
(** [unlines_gen gen] concatenates all strings of [gen], separated with '\n'.
@since 0.10 *)
val set : string -> int -> char -> string
@ -206,79 +211,80 @@ val set : string -> int -> char -> string
@since 0.12 *)
val iter : f:(char -> unit) -> string -> unit
(** Alias to {!String.iter}.
(** [iter ~f s] applies function [f] on each character of [s].
Alias to {!String.iter}.
@since 0.12 *)
val filter_map : f:(char -> char option) -> string -> string
(** [filter_map f s] calls [(f a0) (f a1)(f an)] where [a0 … an] are the characters of s.
(** [filter_map ~f s] calls [(f a0) (f a1)(f an)] where [a0 … an] are the characters of s.
It returns the string of characters [ci] such as [f ai = Some ci] (when [f] returns [None],
the corresponding element of [s] is discarded).
@since 0.17 *)
val filter : f:(char -> bool) -> string -> string
(** [filter f s] discards characters not satisfying [f].
(** [filter ~f s] discards characters of [s] not satisfying [f].
@since 0.17 *)
val flat_map : ?sep:string -> f:(char -> string) -> string -> string
(** Map each chars to a string, then concatenates them all.
(** [flat_map ?sep ~f s] maps each chars of [s] to a string, then concatenates them all.
@param sep optional separator between each generated string.
@since 0.12 *)
val for_all : f:(char -> bool) -> string -> bool
(** True for all chars?
(** [for_all ~f s] is [true] iff all characters of [s] satisfy the predicate [f].
@since 0.12 *)
val exists : f:(char -> bool) -> string -> bool
(** True for some char?
(** [exists ~f s] is [true] iff some character of [s] satisfy the predicate [f].
@since 0.12 *)
val drop_while : f:(char -> bool) -> t -> t
(** [drop_while f s] discards any characters starting from the left,
(** [drop_while ~f s] discards any characters of [s] starting from the left,
up to the first character [c] not satisfying [f c].
@since 2.2 *)
val rdrop_while : f:(char -> bool) -> t -> t
(** [rdrop_while f s] discards any characters starting from the right,
(** [rdrop_while ~f s] discards any characters of [s] starting from the right,
up to the first character [c] not satisfying [f c].
@since 2.2 *)
val ltrim : t -> t
(** Trim space on the left (see {!String.trim} for more details).
(** [ltrim s] trims space on the left (see {!String.trim} for more details).
@since 1.2 *)
val rtrim : t -> t
(** Trim space on the right (see {!String.trim} for more details).
(** [rtrim s] trims space on the right (see {!String.trim} for more details).
@since 1.2 *)
(** {2 Operations on 2 strings} *)
val map2 : f:(char -> char -> char) -> string -> string -> string
(** Map pairs of chars.
(** [map2 ~f s1 s2] maps pairs of chars.
@raise Invalid_argument if the strings have not the same length.
@since 0.12 *)
val iter2: f:(char -> char -> unit) -> string -> string -> unit
(** Iterate on pairs of chars.
(** [iter2 ~f s1 s2] iterates on pairs of chars.
@raise Invalid_argument if the strings have not the same length.
@since 0.12 *)
val iteri2: f:(int -> char -> char -> unit) -> string -> string -> unit
(** Iterate on pairs of chars with their index.
(** [iteri2 ~f s1 s2] iterates on pairs of chars with their index.
@raise Invalid_argument if the strings have not the same length.
@since 0.12 *)
val fold2: f:('a -> char -> char -> 'a) -> init:'a -> string -> string -> 'a
(** Fold on pairs of chars.
(** [fold2 ~f ~init s1 s2] folds on pairs of chars.
@raise Invalid_argument if the strings have not the same length.
@since 0.12 *)
val for_all2 : f:(char -> char -> bool) -> string -> string -> bool
(** All pairs of chars respect the predicate?
(** [for_all2 ~f s1 s2] returns [true] iff all pairs of chars satisfy the predicate [f].
@raise Invalid_argument if the strings have not the same length.
@since 0.12 *)
val exists2 : f:(char -> char -> bool) -> string -> string -> bool
(** Exists a pair of chars?
(** [exists2 ~f s1 s2] returns [true] iff a pair of chars satisfy the predicate [f].
@raise Invalid_argument if the strings have not the same length.
@since 0.12 *)
@ -288,23 +294,31 @@ val exists2 : f:(char -> char -> bool) -> string -> string -> bool
a stable alias for them even in older versions. *)
val capitalize_ascii : string -> string
(** See {!String}.
(** [capitalize_ascii s] returns a copy of [s] with the first character set to uppercase
using the US-ASCII character set.
See {!String}.
@since 0.18 *)
val uncapitalize_ascii : string -> string
(** See {!String}.
(** [uncapitalize_ascii s] returns a copy of [s] with the first character set to lowercase
using the US-ASCII character set.
See {!String}.
@since 0.18 *)
val uppercase_ascii : string -> string
(** See {!String}.
(** [uppercase_ascii s] returns a copy of [s] with all lowercase letters translated to uppercase
using the US-ASCII character set.
See {!String}.
@since 0.18 *)
val lowercase_ascii : string -> string
(** See {!String}.
(** [lowercase_ascii s] returns a copy of [s] with all uppercase letters translated to lowercase
using the US-ASCII character set.
See {!String}.
@since 0.18 *)
val equal_caseless : string -> string -> bool
(** Comparison without respect to {b ascii} lowercase.
(** [equal_caseless s1 s2] compares [s1] and [s2] without respect to {b ascii} lowercase.
@since 1.2 *)
(** {2 Finding}
@ -320,12 +334,12 @@ module Find : sig
val rcompile : string -> [ `Reverse ] pattern
val find : ?start:int -> pattern:(([`Direct] pattern) [@keep_label]) -> string -> int
(** Search for [pattern] in the string, left-to-right.
(** [find ?start ~pattern s] searches for [pattern] in the string [s], left-to-right.
@return the offset of the first match, -1 otherwise.
@param start offset in string at which we start. *)
val rfind : ?start:int -> pattern:(([`Reverse] pattern) [@keep_label]) -> string -> int
(** Search for [pattern] in the string, right-to-left.
(** [rfind ?start ~pattern s] searches for [pattern] in the string [s], right-to-left.
@return the offset of the start of the first match from the right, -1 otherwise.
@param start right-offset in string at which we start. *)
end
@ -349,25 +363,30 @@ module Split : sig
}
val no_drop : drop_if_empty
(** Do not drop any group, even empty and on borders.
(** [no_drop] does not drop any group, even empty and on borders.
@since 1.5 *)
val list_ : ?drop:drop_if_empty -> by:(string [@keep_label]) -> string -> (string*int*int) list
(** Split the given string along the given separator [by]. Should only
be used with very small separators, otherwise
use {!Containers_string.KMP}.
@return a list of slices [(s,index,length)] that are
(** [list_ ?drop ~by s] splits the given string [s] along the given separator [by].
Should only be used with very small separators, otherwise use {!Containers_string.KMP}.
@return a [list] of slices [(s,index,length)] that are
separated by [by]. {!String.sub} can then be used to actually extract
a string from the slice.
@raise Failure if [by = ""]. *)
val gen : ?drop:drop_if_empty -> by:string -> string -> (string*int*int) gen
(** [gen ?drop ~by s] splits the given string [s] along the given separator [by].
Returns a [gen] of slices. *)
val iter : ?drop:drop_if_empty -> by:string -> string -> (string*int*int) iter
(** @since 2.8 *)
(** [iter ?drop ~by s] splits the given string [s] along the given separator [by].
Returns an [iter] of slices.
@since 2.8 *)
val seq : ?drop:drop_if_empty -> by:string -> string -> (string*int*int) Seq.t
(** Renamed from [std_seq] since 3.0.
(** [seq ?drop ~by s] splits the given string [s] along the given separator [by].
Returns a [Seq.t] of slices.
Renamed from [std_seq] since 3.0.
@since 3.0 *)
(** {4 Copying functions}
@ -376,62 +395,73 @@ module Split : sig
more convenient but less efficient in general. *)
val list_cpy : ?drop:drop_if_empty -> by:string -> string -> string list
(** [list_cpy ?drop ~by s] splits the given string [s] along the given separator [by].
Returns a [list] of strings. *)
val gen_cpy : ?drop:drop_if_empty -> by:string -> string -> string gen
(** [gen_cpy ?drop ~by s] splits the given string [s] along the given separator [by].
Returns a [gen] of strings. *)
val iter_cpy : ?drop:drop_if_empty -> by:string -> string -> string iter
(** @since 2.8 *)
(** [iter_cpy ?drop ~by s] splits the given string [s] along the given separator [by].
Returns an [iter] of strings.
@since 2.8 *)
val seq_cpy : ?drop:drop_if_empty -> by:string -> string -> string Seq.t
(** Renamed from [std_seq_cpy] since 3.0.
(** [seq_cpy ?drop ~by s] splits the given string [s] along the given separator [by].
Returns a [Seq.t] of strings.
Renamed from [std_seq_cpy] since 3.0.
@since 3.0 *)
val left : by:(string [@keep_label]) -> string -> (string * string) option
(** Split on the first occurrence of [by] from the leftmost part of
the string.
(** [left ~by s] splits on the first occurrence of [by] from the leftmost part
of the string [s].
@since 0.12 *)
val left_exn : by:(string [@keep_label]) -> string -> string * string
(** Split on the first occurrence of [by] from the leftmost part of the string.
@raise Not_found if [by] is not part of the string.
(** [left_exn ~by s] splits on the first occurrence of [by] from the leftmost part
of the string [s].
@raise Not_found if [by] is not part of the string [s].
@since 0.16 *)
val right : by:(string [@keep_label]) -> string -> (string * string) option
(** Split on the first occurrence of [by] from the rightmost part of
the string.
(** [right ~by s] splits on the first occurrence of [by] from the rightmost part
of the string [s].
@since 0.12 *)
val right_exn : by:(string [@keep_label]) -> string -> string * string
(** Split on the first occurrence of [by] from the rightmost part of the string.
@raise Not_found if [by] is not part of the string.
(** [right_exn ~by s] splits on the first occurrence of [by] from the rightmost part
of the string [s].
@raise Not_found if [by] is not part of the string [s].
@since 0.16 *)
end
val split_on_char : by:char -> string -> string list
(** Split the string along the given char.
(** [split_on_char ~by s] splits the string [s] along the given char [by].
@since 1.2 *)
val split : by:(string [@keep_label]) -> string -> string list
(** Alias to {!Split.list_cpy}.
(** [split ~by s] splits the string [s] along the given string [by].
Alias to {!Split.list_cpy}.
@since 1.2 *)
(** {2 Utils} *)
val compare_versions : string -> string -> int
(** [compare_versions a b] compares {i version strings} [ a] and [b],
(** [compare_versions s1 s2] compares {i version strings} [s1] and [s2],
considering that numbers are above text.
@since 0.13 *)
val compare_natural : string -> string -> int
(** Natural Sort Order, comparing chunks of digits as natural numbers.
(** [compare_natural s1 s2] is the Natural Sort Order, comparing chunks of digits as natural numbers.
https://en.wikipedia.org/wiki/Natural_sort_order
@since 1.3 *)
val edit_distance : ?cutoff:int -> string -> string -> int
(** Edition distance between two strings. This satisfies the classical
distance axioms: it is always positive, symmetric, and satisfies
the formula [distance a b + distance b c >= distance a c].
(** [edit_distance ?cutoff s1 s2] is the edition distance between the two strings [s1] and [s2].
This satisfies the classical distance axioms: it is always positive, symmetric, and satisfies
the formula [distance s1 s2 + distance s2 s3 >= distance s1 s3].
@param cutoff if provided, it's a cap on both the number of iterations,
and on the result. (since 3.0). This is useful if you just want to
check whether the edit distance is less or equal than 2 (use cutoff of 3).