table of contents
        
      
      
    - Tumbleweed 4.14.2-3.1
- Leap-16.0
- Leap-15.6
| Stdlib.String(3) | OCaml library | Stdlib.String(3) | 
NAME¶
Stdlib.String - no description
Module¶
Module Stdlib.String
Documentation¶
Module String
  
   : (module Stdlib__String)
Strings¶
type t = string
The type for strings.
val make : int -> char -> string
make n c is a string of length n with each index holding the character c .
Raises Invalid_argument if n < 0 or n > Sys.max_string_length .
val init : int -> (int -> char) -> string
init n f is a string of length n with index i holding the character f i (called in increasing index order).
Since 4.02.0
Raises Invalid_argument if n < 0 or n > Sys.max_string_length .
val empty : string
The empty string.
Since 4.13.0
val of_bytes : bytes -> string
Return a new string that contains the same bytes as the given byte sequence.
Since 4.13.0
val to_bytes : string -> bytes
Return a new byte sequence that contains the same bytes as the given string.
Since 4.13.0
val length : string -> int
length s is the length (number of bytes/characters) of s .
val get : string -> int -> char
get s i is the character at index i in s . This is the same as writing s.[i] .
Raises Invalid_argument if i not an index of s .
Concatenating¶
Note. The (^) binary operator concatenates two strings.
val concat : string -> string list -> string
concat sep ss concatenates the list of strings ss , inserting the separator string sep between each.
Raises Invalid_argument if the result is longer than Sys.max_string_length bytes.
val cat : string -> string -> string
cat s1 s2 concatenates s1 and s2 ( s1 ^ s2 ).
Since 4.13.0
Raises Invalid_argument if the result is longer than Sys.max_string_length bytes.
Predicates and comparisons¶
val equal : t -> t -> bool
equal s0 s1 is true if and only if s0 and s1 are character-wise equal.
Since 4.03.0 (4.05.0 in StringLabels)
val compare : t -> t -> int
compare s0 s1 sorts s0 and s1 in lexicographical order. compare behaves like compare on strings but may be more efficient.
val starts_with : prefix:string -> string -> bool
starts_with ~prefix s is true if and only if s starts with prefix .
Since 4.13.0
val ends_with : suffix:string -> string -> bool
ends_with ~suffix s is true if and only if s ends with suffix .
Since 4.13.0
val contains_from : string -> int -> char -> bool
contains_from s start c is true if and only if c appears in s after position start .
Raises Invalid_argument if start is not a valid position in s .
val rcontains_from : string -> int -> char -> bool
rcontains_from s stop c is true if and only if c appears in s before position stop+1 .
Raises Invalid_argument if stop < 0 or stop+1 is not a valid position in s .
val contains : string -> char -> bool
contains s c is String.contains_from s 0 c .
Extracting substrings¶
val sub : string -> int -> int -> string
sub s pos len is a string of length len , containing the substring of s that starts at position pos and has length len .
Raises Invalid_argument if pos and len do not designate a valid substring of s .
val split_on_char : char -> string -> string list
split_on_char sep s is the list of all (possibly empty) substrings of s that are delimited by the character sep .
The function's result is specified by the following invariants:
-The list is not empty.
-Concatenating its elements using sep as a separator
    returns a string equal to the input ( concat (make 1 sep)
  
   (split_on_char sep s) = s ).
-No string in the result contains the sep character.
Since 4.04.0 (4.05.0 in StringLabels)
Transforming¶
val map : (char -> char) -> string -> string
map f s is the string resulting from applying f to all the characters of s in increasing order.
Since 4.00.0
val mapi : (int -> char -> char) -> string -> string
mapi f s is like String.map but the index of the character is also passed to f .
Since 4.02.0
val fold_left : ('a -> char -> 'a) -> 'a -> string -> 'a
fold_left f x s computes f (... (f (f x s.[0]) s.[1]) ...) s.[n-1] , where n is the length of the string s .
Since 4.13.0
val fold_right : (char -> 'a -> 'a) -> string -> 'a -> 'a
fold_right f s x computes f s.[0] (f s.[1] ( ... (f s.[n-1] x) ...)) , where n is the length of the string s .
Since 4.13.0
val for_all : (char -> bool) -> string -> bool
for_all p s checks if all characters in s satisfy the predicate p .
Since 4.13.0
val exists : (char -> bool) -> string -> bool
exists p s checks if at least one character of s satisfies the predicate p .
Since 4.13.0
val trim : string -> string
trim s is s without leading and trailing whitespace. Whitespace characters are: ' ' , '\x0C' (form feed), '\n' , '\r' , and '\t' .
Since 4.00.0
val escaped : string -> string
escaped s is s with special characters represented by escape sequences, following the lexical conventions of OCaml.
All characters outside the US-ASCII printable range [0x20;0x7E] are escaped, as well as backslash (0x2F) and double-quote (0x22).
The function Scanf.unescaped is a left inverse of escaped , i.e. Scanf.unescaped (escaped s) = s for any string s (unless escaped s fails).
Raises Invalid_argument if the result is longer than Sys.max_string_length bytes.
val uppercase_ascii : string -> string
uppercase_ascii s is s with all lowercase letters translated to uppercase, using the US-ASCII character set.
Since 4.03.0 (4.05.0 in StringLabels)
val lowercase_ascii : string -> string
lowercase_ascii s is s with all uppercase letters translated to lowercase, using the US-ASCII character set.
Since 4.03.0 (4.05.0 in StringLabels)
val capitalize_ascii : string -> string
capitalize_ascii s is s with the first character set to uppercase, using the US-ASCII character set.
Since 4.03.0 (4.05.0 in StringLabels)
val uncapitalize_ascii : string -> string
uncapitalize_ascii s is s with the first character set to lowercase, using the US-ASCII character set.
Since 4.03.0 (4.05.0 in StringLabels)
Traversing¶
val iter : (char -> unit) -> string -> unit
iter f s applies function f in turn to all the characters of s . It is equivalent to f s.[0]; f s.[1]; ...; f s.[length s - 1]; () .
val iteri : (int -> char -> unit) -> string -> unit
iteri is like String.iter , but the function is also given the corresponding character index.
Since 4.00.0
Searching¶
val index_from : string -> int -> char -> int
index_from s i c is the index of the first occurrence of c in s after position i .
Raises Not_found if c does not occur in s after position i .
Raises Invalid_argument if i is not a valid position in s .
val index_from_opt : string -> int -> char -> int option
index_from_opt s i c is the index of the first occurrence of c in s after position i (if any).
Since 4.05
Raises Invalid_argument if i is not a valid position in s .
val rindex_from : string -> int -> char -> int
rindex_from s i c is the index of the last occurrence of c in s before position i+1 .
Raises Not_found if c does not occur in s before position i+1 .
Raises Invalid_argument if i+1 is not a valid position in s .
val rindex_from_opt : string -> int -> char -> int option
rindex_from_opt s i c is the index of the last occurrence of c in s before position i+1 (if any).
Since 4.05
Raises Invalid_argument if i+1 is not a valid position in s .
val index : string -> char -> int
index s c is String.index_from s 0 c .
val index_opt : string -> char -> int option
index_opt s c is String.index_from_opt s 0 c .
Since 4.05
val rindex : string -> char -> int
rindex s c is String.rindex_from s (length s - 1) c .
val rindex_opt : string -> char -> int option
rindex_opt s c is String.rindex_from_opt s (length s - 1) c .
Since 4.05
Strings and Sequences¶
val to_seq : t -> char Seq.t
to_seq s is a sequence made of the string's characters in increasing order. In "unsafe-string" mode, modifications of the string during iteration will be reflected in the sequence.
Since 4.07
val to_seqi : t -> (int * char) Seq.t
to_seqi s is like String.to_seq but also tuples the corresponding index.
Since 4.07
val of_seq : char Seq.t -> t
of_seq s is a string made of the sequence's characters.
Since 4.07
UTF decoding and validations¶
UTF-8¶
val get_utf_8_uchar : t -> int -> Uchar.utf_decode
get_utf_8_uchar b i decodes an UTF-8 character at index i in b .
val is_valid_utf_8 : t -> bool
is_valid_utf_8 b is true if and only if b contains valid UTF-8 data.
UTF-16BE¶
val get_utf_16be_uchar : t -> int -> Uchar.utf_decode
get_utf_16be_uchar b i decodes an UTF-16BE character at index i in b .
val is_valid_utf_16be : t -> bool
is_valid_utf_16be b is true if and only if b contains valid UTF-16BE data.
UTF-16LE¶
val get_utf_16le_uchar : t -> int -> Uchar.utf_decode
get_utf_16le_uchar b i decodes an UTF-16LE character at index i in b .
val is_valid_utf_16le : t -> bool
is_valid_utf_16le b is true if and only if b contains valid UTF-16LE data.
Deprecated functions¶
val create : int -> bytes
Deprecated. This is a deprecated alias of Bytes.create / BytesLabels.create .
create n returns a fresh byte sequence of length n . The sequence is uninitialized and contains arbitrary bytes.
Raises Invalid_argument if n < 0 or n > Sys.max_string_length .
val set : bytes -> int -> char -> unit
Deprecated. This is a deprecated alias of Bytes.set / BytesLabels.set .
set s n c modifies byte sequence s in place, replacing the byte at index n with c . You can also write s.[n] <- c instead of set s n c .
Raises Invalid_argument if n is not a valid index in s .
val blit : string -> int -> bytes -> int -> int -> unit
blit src src_pos dst dst_pos len copies len bytes from the string src , starting at index src_pos , to byte sequence dst , starting at character number dst_pos .
Raises Invalid_argument if src_pos and len do not designate a valid range of src , or if dst_pos and len do not designate a valid range of dst .
val copy : string -> string
Deprecated. Because strings are immutable, it doesn't make much sense to make identical copies of them.
Return a copy of the given string.
val fill : bytes -> int -> int -> char -> unit
Deprecated. This is a deprecated alias of Bytes.fill / BytesLabels.fill .
fill s pos len c modifies byte sequence s in place, replacing len bytes by c , starting at pos .
Raises Invalid_argument if pos and len do not designate a valid substring of s .
val uppercase : string -> string
Deprecated. Functions operating on Latin-1 character set are deprecated.
Return a copy of the argument, with all lowercase letters translated to uppercase, including accented letters of the ISO Latin-1 (8859-1) character set.
val lowercase : string -> string
Deprecated. Functions operating on Latin-1 character set are deprecated.
Return a copy of the argument, with all uppercase letters translated to lowercase, including accented letters of the ISO Latin-1 (8859-1) character set.
val capitalize : string -> string
Deprecated. Functions operating on Latin-1 character set are deprecated.
Return a copy of the argument, with the first character set to uppercase, using the ISO Latin-1 (8859-1) character set..
val uncapitalize : string -> string
Deprecated. Functions operating on Latin-1 character set are deprecated.
Return a copy of the argument, with the first character set to lowercase, using the ISO Latin-1 (8859-1) character set.
Binary decoding of integers¶
The functions in this section binary decode integers from strings.
All following functions raise Invalid_argument if the characters needed at index i to decode the integer are not available.
Little-endian (resp. big-endian) encoding means that least (resp. most) significant bytes are stored first. Big-endian is also known as network byte order. Native-endian encoding is either little-endian or big-endian depending on Sys.big_endian .
32-bit and 64-bit integers are represented by the int32 and int64 types, which can be interpreted either as signed or unsigned numbers.
8-bit and 16-bit integers are represented by the int type, which has more bits than the binary encoding. These extra bits are sign-extended (or zero-extended) for functions which decode 8-bit or 16-bit integers and represented them with int values.
val get_uint8 : string -> int -> int
get_uint8 b i is b 's unsigned 8-bit integer starting at character index i .
Since 4.13.0
val get_int8 : string -> int -> int
get_int8 b i is b 's signed 8-bit integer starting at character index i .
Since 4.13.0
val get_uint16_ne : string -> int -> int
get_uint16_ne b i is b 's native-endian unsigned 16-bit integer starting at character index i .
Since 4.13.0
val get_uint16_be : string -> int -> int
get_uint16_be b i is b 's big-endian unsigned 16-bit integer starting at character index i .
Since 4.13.0
val get_uint16_le : string -> int -> int
get_uint16_le b i is b 's little-endian unsigned 16-bit integer starting at character index i .
Since 4.13.0
val get_int16_ne : string -> int -> int
get_int16_ne b i is b 's native-endian signed 16-bit integer starting at character index i .
Since 4.13.0
val get_int16_be : string -> int -> int
get_int16_be b i is b 's big-endian signed 16-bit integer starting at character index i .
Since 4.13.0
val get_int16_le : string -> int -> int
get_int16_le b i is b 's little-endian signed 16-bit integer starting at character index i .
Since 4.13.0
val get_int32_ne : string -> int -> int32
get_int32_ne b i is b 's native-endian 32-bit integer starting at character index i .
Since 4.13.0
val get_int32_be : string -> int -> int32
get_int32_be b i is b 's big-endian 32-bit integer starting at character index i .
Since 4.13.0
val get_int32_le : string -> int -> int32
get_int32_le b i is b 's little-endian 32-bit integer starting at character index i .
Since 4.13.0
val get_int64_ne : string -> int -> int64
get_int64_ne b i is b 's native-endian 64-bit integer starting at character index i .
Since 4.13.0
val get_int64_be : string -> int -> int64
get_int64_be b i is b 's big-endian 64-bit integer starting at character index i .
Since 4.13.0
val get_int64_le : string -> int -> int64
get_int64_le b i is b 's little-endian 64-bit integer starting at character index i .
Since 4.13.0
| 2025-03-03 | OCamldoc |