diff options
Diffstat (limited to 'stdlib/buffer.mli')
-rw-r--r-- | stdlib/buffer.mli | 41 |
1 files changed, 26 insertions, 15 deletions
diff --git a/stdlib/buffer.mli b/stdlib/buffer.mli index c50c98792..e7ce8b999 100644 --- a/stdlib/buffer.mli +++ b/stdlib/buffer.mli @@ -11,9 +11,9 @@ (* *) (***********************************************************************) -(** Extensible string buffers. +(** Extensible buffers. - This module implements string buffers that automatically expand + This module implements buffers that automatically expand as necessary. It provides accumulative concatenation of strings in quasi-linear time (instead of quadratic time when strings are concatenated pairwise). @@ -24,8 +24,8 @@ type t val create : int -> t (** [create n] returns a fresh buffer, initially empty. - The [n] parameter is the initial size of the internal string - that holds the buffer contents. That string is automatically + The [n] parameter is the initial size of the internal byte sequence + that holds the buffer contents. That byte sequence is automatically reallocated when more than [n] characters are stored in the buffer, but shrinks back to [n] characters when [reset] is called. For best performance, [n] should be of the same order of magnitude @@ -40,26 +40,30 @@ val contents : t -> string (** Return a copy of the current contents of the buffer. The buffer itself is unchanged. *) +val to_bytes : t -> bytes +(** Return a copy of the current contents of the buffer. + The buffer itself is unchanged. *) + val sub : t -> int -> int -> string -(** [Buffer.sub b off len] returns (a copy of) the substring of the -current contents of the buffer [b] starting at offset [off] of length -[len] bytes. May raise [Invalid_argument] if out of bounds request. The -buffer itself is unaffected. *) +(** [Buffer.sub b off len] returns (a copy of) the bytes from the + current contents of the buffer [b] starting at offset [off] of + length [len] bytes. May raise [Invalid_argument] if out of bounds + request. The buffer itself is unaffected. *) -val blit : t -> int -> string -> int -> int -> unit +val blit : t -> int -> bytes -> int -> int -> unit (** [Buffer.blit src srcoff dst dstoff len] copies [len] characters from the current contents of the buffer [src], starting at offset [srcoff] - to string [dst], starting at character [dstoff]. + to [dst], starting at character [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 - substring of [dst]. + range of [src], or if [dstoff] and [len] do not designate a valid + range of [dst]. @since 3.11.2 *) val nth : t -> int -> char (** get the n-th character of the buffer. Raise [Invalid_argument] if -index out of bounds *) + index out of bounds *) val length : t -> int (** Return the number of characters currently contained in the buffer. *) @@ -68,8 +72,8 @@ val clear : t -> unit (** Empty the buffer. *) val reset : t -> unit -(** Empty the buffer and deallocate the internal string holding the - buffer contents, replacing it with the initial internal string +(** Empty the buffer and deallocate the internal byte sequence holding the + buffer contents, replacing it with the initial internal byte sequence of length [n] that was allocated by {!Buffer.create} [n]. For long-lived buffers that may have grown a lot, [reset] allows faster reclamation of the space used by the buffer. *) @@ -80,10 +84,17 @@ val add_char : t -> char -> unit val add_string : t -> string -> unit (** [add_string b s] appends the string [s] at the end of the buffer [b]. *) +val add_bytes : t -> bytes -> unit +(** [add_string b s] appends the string [s] at the end of the buffer [b]. *) + val add_substring : t -> string -> int -> int -> unit (** [add_substring b s ofs len] takes [len] characters from offset [ofs] in string [s] and appends them at the end of the buffer [b]. *) +val add_subbytes : t -> bytes -> int -> int -> unit +(** [add_substring b s ofs len] takes [len] characters from offset + [ofs] in byte sequence [s] and appends them at the end of the buffer [b]. *) + val add_substitute : t -> (string -> string) -> string -> unit (** [add_substitute b f s] appends the string pattern [s] at the end of the buffer [b] with substitution. |