diff options
author | Damien Doligez <damien.doligez-inria.fr> | 1997-09-11 15:10:23 +0000 |
---|---|---|
committer | Damien Doligez <damien.doligez-inria.fr> | 1997-09-11 15:10:23 +0000 |
commit | c44e6f999a4b06a4b0e961e8607ab8c557501a57 (patch) | |
tree | 3255033ee7995334288ca1ed7cd17d2b1de45451 /stdlib/string.mli | |
parent | 1d41f4abb025864b1aee444790b613cc5f0a444a (diff) |
arg.ml, arg.mli, string.mli: amelioration de la doc
array.mli, array.ml, random.ml: create -> make (coherence avec String)
sys.ml, sys.mli: ajout max_string_length, max_array_length
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@1706 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/string.mli')
-rw-r--r-- | stdlib/string.mli | 14 |
1 files changed, 7 insertions, 7 deletions
diff --git a/stdlib/string.mli b/stdlib/string.mli index 4ac2bca81..d12b52180 100644 --- a/stdlib/string.mli +++ b/stdlib/string.mli @@ -52,14 +52,14 @@ val fill : string -> int -> int -> char -> unit Raise [Invalid_argument] if [start] and [len] do not designate a valid substring of [s]. *) val blit : string -> int -> string -> int -> int -> unit - (* [String.blit s1 o1 s2 o2 len] copies [len] characters - from string [s1], starting at character number [o1], to string [s2], - starting at character number [o2]. It works correctly even if - [s1] and [s2] are the same string, + (* [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 + correctly even if [src] and [dst] are the same string, and the source and destination chunks overlap. - Raise [Invalid_argument] if [o1] and [len] do not - designate a valid substring of [s1], or if [o2] and [len] do not - designate a valid substring of [s2]. *) + 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 substring of [dst]. *) val concat : string -> string list -> string (* [String.concat sep sl] catenates the list of strings [sl], |