diff options
author | Damien Doligez <damien.doligez-inria.fr> | 2014-08-22 13:45:02 +0000 |
---|---|---|
committer | Damien Doligez <damien.doligez-inria.fr> | 2014-08-22 13:45:02 +0000 |
commit | cbfe627f925ab2bab93bae7a7bc9f6ee6afb8637 (patch) | |
tree | af5ec283ac3175b1ab95dd745dbd05f2298b9da6 /stdlib/string.mli | |
parent | 09ad9c1abbe6bee443a55379223280dab3de4749 (diff) |
merge changes from branch 4.02 from branching (rev 14852) to 4.02.0+rc1 (rev 15121)
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15125 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/string.mli')
-rw-r--r-- | stdlib/string.mli | 25 |
1 files changed, 14 insertions, 11 deletions
diff --git a/stdlib/string.mli b/stdlib/string.mli index da6d8351a..8f1e178b5 100644 --- a/stdlib/string.mli +++ b/stdlib/string.mli @@ -90,8 +90,11 @@ val init : int -> (int -> char) -> string @since 4.02.0 *) -val copy : string -> string -(** Return a copy of the given string. *) +val copy : string -> string [@@ocaml.deprecated] +(** Return a copy of the given string. + + @deprecated Because strings are immutable, it doesn't make much + sense to make identical copies of them. *) val sub : string -> int -> int -> string (** [String.sub s start len] returns a fresh string of length [len], @@ -111,17 +114,14 @@ val fill : bytes -> int -> int -> char -> unit [@@ocaml.deprecated] @deprecated This is a deprecated alias of {!Bytes.fill}.[ ] *) val blit : string -> int -> bytes -> int -> int -> unit -(** [String.blit src srcoff dst dstoff len] copies [len] characters - (bytes) from the string [src], starting at index [srcoff], to byte - sequence [dst], starting at index [dstoff]. - - Raise [Invalid_argument] if [srcoff] and [len] do not - designate a valid substring of [src], or if [dstoff] and [len] - do not designate a valid range of [dst]. *) +(** Same as {!Bytes.blit_string}. *) val concat : string -> string list -> string (** [String.concat sep sl] concatenates the list of strings [sl], - inserting the separator string [sep] between each. *) + inserting the separator string [sep] between each. + + Raise [Invalid_argument] if the result is longer than + {!Sys.max_string_length} bytes. *) val iter : (char -> unit) -> string -> unit (** [String.iter f s] applies function [f] in turn to all @@ -159,7 +159,10 @@ val escaped : string -> string represented by escape sequences, following the lexical conventions of OCaml. If there is no special character in the argument, return the original string itself, - not a copy. Its inverse function is Scanf.unescaped. *) + not a copy. Its inverse function is Scanf.unescaped. + + Raise [Invalid_argument] if the result is longer than + {!Sys.max_string_length} bytes. *) val index : string -> char -> int (** [String.index s c] returns the index of the first |