summaryrefslogtreecommitdiffstats
path: root/stdlib/string.mli
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/string.mli')
-rw-r--r--stdlib/string.mli35
1 files changed, 18 insertions, 17 deletions
diff --git a/stdlib/string.mli b/stdlib/string.mli
index c7d0207be..36928a5ca 100644
--- a/stdlib/string.mli
+++ b/stdlib/string.mli
@@ -31,32 +31,32 @@ external set : string -> int -> char -> unit = "%string_safe_set"
0 to [(String.length s - 1)].
You can also write [s.[n] <- c] instead of [String.set s n c]. *)
-external create : int -> string = "create_string"
+external create : len:int -> string = "create_string"
(* [String.create n] returns a fresh string of length [n].
The string initially contains arbitrary characters.
Raise [Invalid_argument] if [n <= 0] or [n > Sys.max_string_length].
*)
-val make : int -> char -> string
+val make : len:int -> char -> string
(* [String.make n c] returns a fresh string of length [n],
filled with the character [c].
Raise [Invalid_argument] if [n <= 0] or [n > Sys.max_string_length].
*)
val copy : string -> string
(* Return a copy of the given string. *)
-val sub : string -> int -> int -> string
+val sub : string -> pos:int -> len:int -> string
(* [String.sub s start len] returns a fresh string of length [len],
containing the characters number [start] to [start + len - 1]
of string [s].
Raise [Invalid_argument] if [start] and [len] do not
designate a valid substring of [s]; that is, if [start < 0],
or [len < 0], or [start + len > String.length s]. *)
-val fill : string -> int -> int -> char -> unit
+val fill : string -> pos:int -> len:int -> char -> unit
(* [String.fill s start len c] modifies string [s] in place,
replacing the characters number [start] to [start + len - 1]
by [c].
Raise [Invalid_argument] if [start] and [len] do not
designate a valid substring of [s]. *)
-val blit : string -> int -> string -> int -> int -> unit
+val blit : string -> pos:int -> to:string -> to_pos:int -> len:int -> unit
(* [String.blit src srcoff dst dstoff len] copies [len] characters
from string [src], starting at character number [srcoff], to
string [dst], starting at character number [dstoff]. It works
@@ -66,7 +66,7 @@ val blit : string -> int -> string -> int -> int -> unit
designate a valid substring of [src], or if [dstoff] and [len]
do not designate a valid substring of [dst]. *)
-val concat : string -> string list -> string
+val concat : sep:string -> string list -> string
(* [String.concat sep sl] catenates the list of strings [sl],
inserting the separator string [sep] between each. *)
@@ -75,31 +75,31 @@ val escaped: string -> string
by escape sequences, following the lexical conventions of
Objective Caml. *)
-val index: string -> char -> int
+val index: string -> elt:char -> int
(* [String.index s c] returns the position of the leftmost
occurrence of character [c] in string [s].
Raise [Not_found] if [c] does not occur in [s]. *)
-val rindex: string -> char -> int
+val rindex: string -> elt:char -> int
(* [String.rindex s c] returns the position of the rightmost
occurrence of character [c] in string [s].
Raise [Not_found] if [c] does not occur in [s]. *)
-val index_from: string -> int -> char -> int
-val rindex_from: string -> int -> char -> int
+val index_from: string -> pos:int -> elt:char -> int
+val rindex_from: string -> pos:int -> elt:char -> int
(* Same as [String.index] and [String.rindex], but start
searching at the character position given as second argument.
[String.index s c] is equivalent to [String.index_from s 0 c],
and [String.rindex s c] to
[String.rindex_from s (String.length s - 1) c]. *)
-val contains : string -> char -> bool
+val contains : string -> elt:char -> bool
(* [String.contains s c] tests if character [c]
appears in the string [s]. *)
-val contains_from : string -> int -> char -> bool
+val contains_from : string -> pos:int -> elt:char -> bool
(* [String.contains_from s start c] tests if character [c]
appears in the substring of [s] starting from [start] to the end
of [s].
Raise [Invalid_argument] if [start] is not a valid index of [s]. *)
-val rcontains_from : string -> int -> char -> bool
+val rcontains_from : string -> pos:int -> elt:char -> bool
(* [String.rcontains_from s stop c] tests if character [c]
appears in the substring of [s] starting from the beginning
of [s] to index [stop].
@@ -124,7 +124,8 @@ val uncapitalize: string -> string
external unsafe_get : string -> int -> char = "%string_unsafe_get"
external unsafe_set : string -> int -> char -> unit = "%string_unsafe_set"
-external unsafe_blit : string -> int -> string -> int -> int -> unit
- = "blit_string" "noalloc"
-external unsafe_fill : string -> int -> int -> char -> unit
- = "fill_string" "noalloc"
+external unsafe_blit :
+ string -> pos:int -> to:string -> to_pos:int -> len:int -> unit
+ = "blit_string" "noalloc"
+external unsafe_fill : string -> pos:int -> len:int -> char -> unit
+ = "fill_string" "noalloc"