diff options
-rw-r--r-- | stdlib/array.mli | 3 | ||||
-rw-r--r-- | stdlib/buffer.mli | 11 | ||||
-rw-r--r-- | stdlib/bytesLabels.mli | 4 | ||||
-rw-r--r-- | stdlib/digest.mli | 6 | ||||
-rw-r--r-- | stdlib/marshal.mli | 6 | ||||
-rw-r--r-- | stdlib/pervasives.mli | 15 | ||||
-rw-r--r-- | stdlib/printexc.mli | 4 | ||||
-rw-r--r-- | stdlib/scanf.mli | 6 | ||||
-rw-r--r-- | stdlib/stream.mli | 3 |
9 files changed, 40 insertions, 18 deletions
diff --git a/stdlib/array.mli b/stdlib/array.mli index 99de0c806..7580f7e75 100644 --- a/stdlib/array.mli +++ b/stdlib/array.mli @@ -154,7 +154,8 @@ val fold_right : ('b -> 'a -> 'a) -> 'b array -> 'a -> 'a external make_float: int -> float array = "caml_make_float_vect" (** [Array.make_float n] returns a fresh float array of length [n], - with uninitialized data. *) + with uninitialized data. + @since 4.02 *) (** {6 Sorting} *) diff --git a/stdlib/buffer.mli b/stdlib/buffer.mli index e7ce8b999..962f6bc7f 100644 --- a/stdlib/buffer.mli +++ b/stdlib/buffer.mli @@ -38,11 +38,12 @@ val create : int -> t val contents : t -> string (** Return a copy of the current contents of the buffer. - The buffer itself is unchanged. *) + 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. *) + The buffer itself is unchanged. + @since 4.02 *) val sub : t -> int -> int -> string (** [Buffer.sub b off len] returns (a copy of) the bytes from the @@ -85,7 +86,8 @@ 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]. *) +(** [add_string b s] appends the string [s] at the end of the buffer [b]. + @since 4.02 *) val add_substring : t -> string -> int -> int -> unit (** [add_substring b s ofs len] takes [len] characters from offset @@ -93,7 +95,8 @@ val add_substring : t -> string -> int -> int -> unit 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]. *) + [ofs] in byte sequence [s] and appends them at the end of the buffer [b]. + @since 4.02 *) val add_substitute : t -> (string -> string) -> string -> unit (** [add_substitute b f s] appends the string pattern [s] at the end diff --git a/stdlib/bytesLabels.mli b/stdlib/bytesLabels.mli index d48d95f5c..04043182f 100644 --- a/stdlib/bytesLabels.mli +++ b/stdlib/bytesLabels.mli @@ -11,7 +11,9 @@ (* *) (***********************************************************************) -(** Byte sequence operations. *) +(** Byte sequence operations. + @since 4.02.0 + *) external length : bytes -> int = "%string_length" (** Return the length (number of bytes) of the argument. *) diff --git a/stdlib/digest.mli b/stdlib/digest.mli index 583d2a46b..9227cd7de 100644 --- a/stdlib/digest.mli +++ b/stdlib/digest.mli @@ -37,7 +37,8 @@ val string : string -> t (** Return the digest of the given string. *) val bytes : bytes -> t -(** Return the digest of the given byte sequence. *) +(** Return the digest of the given byte sequence. + @since 4.02.0 *) val substring : string -> int -> int -> t (** [Digest.substring s ofs len] returns the digest of the substring @@ -45,7 +46,8 @@ val substring : string -> int -> int -> t val subbytes : bytes -> int -> int -> t (** [Digest.subbytes s ofs len] returns the digest of the subsequence - of [s] starting at index [ofs] and containing [len] bytes. *) + of [s] starting at index [ofs] and containing [len] bytes. + @since 4.02.0 *) external channel : in_channel -> int -> t = "caml_md5_chan" (** If [len] is nonnegative, [Digest.channel ic len] reads [len] diff --git a/stdlib/marshal.mli b/stdlib/marshal.mli index 9dfdd1624..4f0ed49b7 100644 --- a/stdlib/marshal.mli +++ b/stdlib/marshal.mli @@ -114,7 +114,8 @@ external to_bytes : (** [Marshal.to_bytes v flags] returns a byte sequence containing the representation of [v]. The [flags] argument has the same meaning as for - {!Marshal.to_channel}. *) + {!Marshal.to_channel}. + @since 4.02.0 *) external to_string : 'a -> extern_flags list -> string = "caml_output_value_to_string" @@ -141,7 +142,8 @@ val from_bytes : bytes -> int -> 'a like {!Marshal.from_channel} does, except that the byte representation is not read from a channel, but taken from the byte sequence [buff], starting at position [ofs]. - The byte sequence is not mutated. *) + The byte sequence is not mutated. + @since 4.02.0 *) val from_string : string -> int -> 'a (** Same as [from_bytes] but take a string as argument instead of a diff --git a/stdlib/pervasives.mli b/stdlib/pervasives.mli index a40b09b8d..9f07c095b 100644 --- a/stdlib/pervasives.mli +++ b/stdlib/pervasives.mli @@ -617,7 +617,8 @@ val print_string : string -> unit (** Print a string on standard output. *) val print_bytes : bytes -> unit -(** Print a byte sequence on standard output. *) +(** Print a byte sequence on standard output. + @since 4.02.0 *) val print_int : int -> unit (** Print an integer, in decimal, on standard output. *) @@ -644,7 +645,8 @@ val prerr_string : string -> unit (** Print a string on standard error. *) val prerr_bytes : bytes -> unit -(** Print a byte sequence on standard error. *) +(** Print a byte sequence on standard error. + @since 4.02.0 *) val prerr_int : int -> unit (** Print an integer, in decimal, on standard error. *) @@ -731,7 +733,8 @@ val output_string : out_channel -> string -> unit (** Write the string on the given output channel. *) val output_bytes : out_channel -> bytes -> unit -(** Write the byte sequence on the given output channel. *) +(** Write the byte sequence on the given output channel. + @since 4.02.0 *) val output : out_channel -> bytes -> int -> int -> unit (** [output oc buf pos len] writes [len] characters from byte sequence [buf], @@ -741,7 +744,8 @@ val output : out_channel -> bytes -> int -> int -> unit val output_substring : out_channel -> string -> int -> int -> unit (** Same as [output] but take a string as argument instead of - a byte sequence. *) + a byte sequence. + @since 4.02.0 *) val output_byte : out_channel -> int -> unit (** Write one 8-bit integer (as the single character with that code) @@ -861,7 +865,8 @@ val really_input_string : in_channel -> int -> string (** [really_input_string ic len] reads [len] characters from channel [ic] and returns them in a new string. Raise [End_of_file] if the end of file is reached before [len] - characters have been read. *) + characters have been read. + @since 4.02.0 *) val input_byte : in_channel -> int (** Same as {!Pervasives.input_char}, but return the 8-bit integer representing diff --git a/stdlib/printexc.mli b/stdlib/printexc.mli index 12e021c23..c347b9915 100644 --- a/stdlib/printexc.mli +++ b/stdlib/printexc.mli @@ -181,6 +181,8 @@ val backtrace_slots : raw_backtrace -> backtrace_slot array option debug information ([-g]) - the program is a bytecode program that has not been linked with debug information enabled ([ocamlc -g]) + + @since 4.02.0 *) type location = { @@ -247,6 +249,8 @@ type raw_backtrace_slot elements are equal, then they represent the same source location (the converse is not necessarily true in presence of inlining, for example). + + @since 4.02.0 *) val raw_backtrace_length : raw_backtrace -> int diff --git a/stdlib/scanf.mli b/stdlib/scanf.mli index 297d6f2d5..212aa00b7 100644 --- a/stdlib/scanf.mli +++ b/stdlib/scanf.mli @@ -488,12 +488,14 @@ val kscanf : val ksscanf : string -> (Scanning.in_channel -> exn -> 'd) -> ('a, 'b, 'c, 'd) scanner -(** Same as {!Scanf.kscanf} but reads from the given string. *) +(** Same as {!Scanf.kscanf} but reads from the given string. + @since 4.02.0 *) val kfscanf : Pervasives.in_channel -> (Scanning.in_channel -> exn -> 'd) -> ('a, 'b, 'c, 'd) scanner -(** Same as {!Scanf.kscanf}, but reads from the given regular input channel. *) +(** Same as {!Scanf.kscanf}, but reads from the given regular input channel. + @since 4.02.0 *) (** {6 Reading format strings from input} *) diff --git a/stdlib/stream.mli b/stdlib/stream.mli index 85a846102..1957cf60d 100644 --- a/stdlib/stream.mli +++ b/stdlib/stream.mli @@ -47,7 +47,8 @@ val of_string : string -> char t (** Return the stream of the characters of the string parameter. *) val of_bytes : bytes -> char t -(** Return the stream of the characters of the bytes parameter. *) +(** Return the stream of the characters of the bytes parameter. + @since 4.02.0 *) val of_channel : in_channel -> char t (** Return the stream of the characters read from the input channel. *) |