remove double @sinces

master
John Whitington 2020-08-03 15:26:44 +01:00
parent da7e2131dc
commit 53f753d772
10 changed files with 44 additions and 88 deletions

View File

@ -145,8 +145,7 @@ val unsafe_environment : unit -> string array
privileges. See the documentation for {!unsafe_getenv} for more
details.
@since 4.12.0
@since 4.06.0 *)
@since 4.06.0 (4.12.0 in UnixLabels) *)
val getenv : string -> string
(** Return the value associated to a variable in the process
@ -327,8 +326,7 @@ val close : file_descr -> unit
val fsync : file_descr -> unit
(** Flush file buffers to disk.
@since 4.12.0
@since 4.08.0 *)
@since 4.08.0 (4.12.0 in UnixLabels) *)
val read : file_descr -> bytes -> int -> int -> int
(** [read fd buf pos len] reads [len] bytes from descriptor [fd],
@ -887,29 +885,25 @@ val process_in_pid : in_channel -> int
(** Return the pid of a process opened via {!open_process_in} or
{!open_process_args_in}.
@since 4.12.0
@since 4.08.0 *)
@since 4.08.0 (4.12.0 in UnixLabels) *)
val process_out_pid : out_channel -> int
(** Return the pid of a process opened via {!open_process_out} or
{!open_process_args_out}.
@since 4.12.0
@since 4.08.0 *)
@since 4.08.0 (4.12.0 in UnixLabels) *)
val process_pid : in_channel * out_channel -> int
(** Return the pid of a process opened via {!open_process} or
{!open_process_args}.
@since 4.12.0
@since 4.08.0 *)
@since 4.08.0 (4.12.0 in UnixLabels) *)
val process_full_pid : in_channel * out_channel * in_channel -> int
(** Return the pid of a process opened via {!open_process_full} or
{!open_process_args_full}.
@since 4.12.0
@since 4.08.0 *)
@since 4.08.0 (4.12.0 in UnixLabels) *)
val close_process_in : in_channel -> process_status
(** Close channels opened by {!open_process_in},
@ -1155,8 +1149,7 @@ val sleepf : float -> unit
(** Stop execution for the given number of seconds. Like [sleep],
but fractions of seconds are supported.
@since 4.03.0
@since 4.12.0 *)
@since 4.03.0 (4.12.0 in UnixLabels) *)
val times : unit -> process_times
(** Return the execution times of the process.

View File

@ -145,8 +145,7 @@ val unsafe_environment : unit -> string array
privileges. See the documentation for {!unsafe_getenv} for more
details.
@since 4.12.0
@sinceunlabelednowarn 4.06.0 *)
@since 4.06.0 (4.12.0 in UnixLabels) *)
val getenv : string -> string
(** Return the value associated to a variable in the process
@ -327,8 +326,7 @@ val close : file_descr -> unit
val fsync : file_descr -> unit
(** Flush file buffers to disk.
@since 4.12.0
@sinceunlabelednowarn 4.08.0 *)
@since 4.08.0 (4.12.0 in UnixLabels) *)
val read : file_descr -> buf:bytes -> pos:int -> len:int -> int
(** [read fd ~buf ~pos ~len] reads [len] bytes from descriptor [fd],
@ -887,29 +885,25 @@ val process_in_pid : in_channel -> int
(** Return the pid of a process opened via {!open_process_in} or
{!open_process_args_in}.
@since 4.12.0
@sinceunlabelednowarn 4.08.0 *)
@since 4.08.0 (4.12.0 in UnixLabels) *)
val process_out_pid : out_channel -> int
(** Return the pid of a process opened via {!open_process_out} or
{!open_process_args_out}.
@since 4.12.0
@sinceunlabelednowarn 4.08.0 *)
@since 4.08.0 (4.12.0 in UnixLabels) *)
val process_pid : in_channel * out_channel -> int
(** Return the pid of a process opened via {!open_process} or
{!open_process_args}.
@since 4.12.0
@sinceunlabelednowarn 4.08.0 *)
@since 4.08.0 (4.12.0 in UnixLabels) *)
val process_full_pid : in_channel * out_channel * in_channel -> int
(** Return the pid of a process opened via {!open_process_full} or
{!open_process_args_full}.
@since 4.12.0
@sinceunlabelednowarn 4.08.0 *)
@since 4.08.0 (4.12.0 in UnixLabels) *)
val close_process_in : in_channel -> process_status
(** Close channels opened by {!open_process_in},
@ -1155,8 +1149,7 @@ val sleepf : float -> unit
(** Stop execution for the given number of seconds. Like [sleep],
but fractions of seconds are supported.
@since 4.03.0
@sinceunlabelednowarn 4.12.0 *)
@since 4.03.0 (4.12.0 in UnixLabels) *)
val times : unit -> process_times
(** Return the execution times of the process.

View File

@ -204,8 +204,7 @@ val iter2 : ('a -> 'b -> unit) -> 'a array -> 'b array -> unit
(** [iter2 f a b] applies function [f] to all the elements of [a]
and [b].
@raise Invalid_argument if the arrays are not the same size.
@since 4.05.0
@since 4.03.0
@since 4.03.0 (4.05.0 in ArrayLabels)
*)
val map2 : ('a -> 'b -> 'c) -> 'a array -> 'b array -> 'c array
@ -213,8 +212,7 @@ val map2 : ('a -> 'b -> 'c) -> 'a array -> 'b array -> 'c array
and [b], and builds an array with the results returned by [f]:
[[| f a.(0) b.(0); ...; f a.(length a - 1) b.(length b - 1)|]].
@raise Invalid_argument if the arrays are not the same size.
@since 4.05.0
@since 4.03.0 *)
@since 4.03.0 (4.05.0 in ArrayLabels) *)
(** {1 Array scanning} *)

View File

@ -204,8 +204,7 @@ val iter2 : f:('a -> 'b -> unit) -> 'a array -> 'b array -> unit
(** [iter2 ~f a b] applies function [f] to all the elements of [a]
and [b].
@raise Invalid_argument if the arrays are not the same size.
@since 4.05.0
@sinceunlabelednowarn 4.03.0
@since 4.03.0 (4.05.0 in ArrayLabels)
*)
val map2 : f:('a -> 'b -> 'c) -> 'a array -> 'b array -> 'c array
@ -213,8 +212,7 @@ val map2 : f:('a -> 'b -> 'c) -> 'a array -> 'b array -> 'c array
and [b], and builds an array with the results returned by [f]:
[[| f a.(0) b.(0); ...; f a.(length a - 1) b.(length b - 1)|]].
@raise Invalid_argument if the arrays are not the same size.
@since 4.05.0
@sinceunlabelednowarn 4.03.0 *)
@since 4.03.0 (4.05.0 in ArrayLabels) *)
(** {1 Array scanning} *)

View File

@ -298,26 +298,22 @@ val uncapitalize : bytes -> bytes
val uppercase_ascii : bytes -> bytes
(** Return a copy of the argument, with all lowercase letters
translated to uppercase, using the US-ASCII character set.
@since 4.05.0
@since 4.03.0 *)
@since 4.03.0 (4.05.0 in BytesLabels) *)
val lowercase_ascii : bytes -> bytes
(** Return a copy of the argument, with all uppercase letters
translated to lowercase, using the US-ASCII character set.
@since 4.05.0
@since 4.03.0 *)
@since 4.03.0 (4.05.0 in BytesLabels) *)
val capitalize_ascii : bytes -> bytes
(** Return a copy of the argument, with the first character set to uppercase,
using the US-ASCII character set.
@since 4.05.0
@since 4.03.0 *)
@since 4.03.0 (4.05.0 in BytesLabels) *)
val uncapitalize_ascii : bytes -> bytes
(** Return a copy of the argument, with the first character set to lowercase,
using the US-ASCII character set.
@since 4.05.0
@since 4.03.0 *)
@since 4.03.0 (4.05.0 in BytesLabels) *)
type t = bytes
(** An alias for the type of byte sequences. *)
@ -330,8 +326,7 @@ val compare: t -> t -> int
val equal: t -> t -> bool
(** The equality function for byte sequences.
@since 4.05.0
@since 4.03.0 *)
@since 4.03.0 (4.05.0 in BytesLabels) *)
(** {1:unsafe Unsafe conversions (for advanced users)}

View File

@ -298,26 +298,22 @@ val uncapitalize : bytes -> bytes
val uppercase_ascii : bytes -> bytes
(** Return a copy of the argument, with all lowercase letters
translated to uppercase, using the US-ASCII character set.
@since 4.05.0
@sinceunlabelednowarn 4.03.0 *)
@since 4.03.0 (4.05.0 in BytesLabels) *)
val lowercase_ascii : bytes -> bytes
(** Return a copy of the argument, with all uppercase letters
translated to lowercase, using the US-ASCII character set.
@since 4.05.0
@sinceunlabelednowarn 4.03.0 *)
@since 4.03.0 (4.05.0 in BytesLabels) *)
val capitalize_ascii : bytes -> bytes
(** Return a copy of the argument, with the first character set to uppercase,
using the US-ASCII character set.
@since 4.05.0
@sinceunlabelednowarn 4.03.0 *)
@since 4.03.0 (4.05.0 in BytesLabels) *)
val uncapitalize_ascii : bytes -> bytes
(** Return a copy of the argument, with the first character set to lowercase,
using the US-ASCII character set.
@since 4.05.0
@sinceunlabelednowarn 4.03.0 *)
@since 4.03.0 (4.05.0 in BytesLabels) *)
type t = bytes
(** An alias for the type of byte sequences. *)
@ -330,8 +326,7 @@ val compare: t -> t -> int
val equal: t -> t -> bool
(** The equality function for byte sequences.
@since 4.05.0
@sinceunlabelednowarn 4.03.0 *)
@since 4.03.0 (4.05.0 in BytesLabels) *)
(** {1:unsafe Unsafe conversions (for advanced users)}

View File

@ -67,8 +67,7 @@ val compare_length_with : 'a list -> int -> int
val cons : 'a -> 'a list -> 'a list
(** [cons x xs] is [x :: xs]
@since 4.05.0
@since 4.03.0
@since 4.03.0 (4.05.0 in ListLabels)
*)
val hd : 'a list -> 'a
@ -435,8 +434,7 @@ val fast_sort : ('a -> 'a -> int) -> 'a list -> 'a list
val sort_uniq : ('a -> 'a -> int) -> 'a list -> 'a list
(** Same as {!sort}, but also remove duplicates.
@since 4.03.0
@since 4.02.0
@since 4.02.0 (4.03.0 in ListLabels)
*)
val merge : ('a -> 'a -> int) -> 'a list -> 'a list -> 'a list

View File

@ -67,8 +67,7 @@ val compare_length_with : 'a list -> len:int -> int
val cons : 'a -> 'a list -> 'a list
(** [cons x xs] is [x :: xs]
@since 4.05.0
@sinceunlabelednowarn 4.03.0
@since 4.03.0 (4.05.0 in ListLabels)
*)
val hd : 'a list -> 'a
@ -435,8 +434,7 @@ val fast_sort : cmp:('a -> 'a -> int) -> 'a list -> 'a list
val sort_uniq : cmp:('a -> 'a -> int) -> 'a list -> 'a list
(** Same as {!sort}, but also remove duplicates.
@since 4.03.0
@sinceunlabelednowarn 4.02.0
@since 4.02.0 (4.03.0 in ListLabels)
*)
val merge : cmp:('a -> 'a -> int) -> 'a list -> 'a list -> 'a list

View File

@ -302,26 +302,22 @@ val uncapitalize : string -> string
val uppercase_ascii : string -> string
(** Return a copy of the argument, with all lowercase letters
translated to uppercase, using the US-ASCII character set.
@since 4.05.0
@since 4.03.0 *)
@since 4.03.0 (4.05.0 in StringLabels) *)
val lowercase_ascii : string -> string
(** Return a copy of the argument, with all uppercase letters
translated to lowercase, using the US-ASCII character set.
@since 4.05.0
@since 4.03.0 *)
@since 4.03.0 (4.05.0 in StringLabels) *)
val capitalize_ascii : string -> string
(** Return a copy of the argument, with the first character set to uppercase,
using the US-ASCII character set.
@since 4.05.0
@since 4.03.0 *)
@since 4.03.0 (4.05.0 in StringLabels) *)
val uncapitalize_ascii : string -> string
(** Return a copy of the argument, with the first character set to lowercase,
using the US-ASCII character set.
@since 4.05.0
@since 4.03.0 *)
@since 4.03.0 (4.05.0 in StringLabels) *)
val starts_with :
prefix (* comment thwarts tools/unlabel *) :string -> string -> bool
@ -345,8 +341,7 @@ val split_on_char: char -> string -> string list
(split_on_char sep s) = s]).
- No string in the result contains the [sep] character.
@since 4.05.0
@since 4.04.0
@since 4.04.0 (4.05.0 in StringLabels)
*)
type t = string
@ -360,8 +355,7 @@ val compare: t -> t -> int
val equal: t -> t -> bool
(** The equal function for strings.
@since 4.05.0
@since 4.03.0 *)
@since 4.03.0 (4.05.0 in StringLabels) *)
(** {1 Iterators} *)

View File

@ -302,26 +302,22 @@ val uncapitalize : string -> string
val uppercase_ascii : string -> string
(** Return a copy of the argument, with all lowercase letters
translated to uppercase, using the US-ASCII character set.
@since 4.05.0
@sinceunlabelednowarn 4.03.0 *)
@since 4.03.0 (4.05.0 in StringLabels) *)
val lowercase_ascii : string -> string
(** Return a copy of the argument, with all uppercase letters
translated to lowercase, using the US-ASCII character set.
@since 4.05.0
@sinceunlabelednowarn 4.03.0 *)
@since 4.03.0 (4.05.0 in StringLabels) *)
val capitalize_ascii : string -> string
(** Return a copy of the argument, with the first character set to uppercase,
using the US-ASCII character set.
@since 4.05.0
@sinceunlabelednowarn 4.03.0 *)
@since 4.03.0 (4.05.0 in StringLabels) *)
val uncapitalize_ascii : string -> string
(** Return a copy of the argument, with the first character set to lowercase,
using the US-ASCII character set.
@since 4.05.0
@sinceunlabelednowarn 4.03.0 *)
@since 4.03.0 (4.05.0 in StringLabels) *)
val starts_with :
prefix (* comment thwarts tools/unlabel *) :string -> string -> bool
@ -345,8 +341,7 @@ val split_on_char: sep:char -> string -> string list
(split_on_char sep s) = s]).
- No string in the result contains the [sep] character.
@since 4.05.0
@sinceunlabelednowarn 4.04.0
@since 4.04.0 (4.05.0 in StringLabels)
*)
type t = string
@ -360,8 +355,7 @@ val compare: t -> t -> int
val equal: t -> t -> bool
(** The equal function for strings.
@since 4.05.0
@sinceunlabelednowarn 4.03.0 *)
@since 4.03.0 (4.05.0 in StringLabels) *)
(** {1 Iterators} *)