Labeled and unlabeled @sinces automatically

master
John Whitington 2020-07-30 17:21:22 +01:00
parent 0fbeee11be
commit 6e0557f6d7
11 changed files with 125 additions and 62 deletions

View File

@ -150,7 +150,8 @@ val unsafe_environment : unit -> string array
privileges. See the documentation for {!unsafe_getenv} for more
details.
@since 4.06.0 in unlabeled module, 4.12.0 in labeled *)
@since 4.12.0
@since 4.06.0 *)
val getenv : string -> string
(** Return the value associated to a variable in the process
@ -331,7 +332,8 @@ val close : file_descr -> unit
val fsync : file_descr -> unit
(** Flush file buffers to disk.
@since 4.08.0 in unlabeled module, 4.12.0 in labeled *)
@since 4.12.0
@since 4.08.0 *)
val read : file_descr -> bytes -> int -> int -> int
(** [read fd buf pos len] reads [len] bytes from descriptor [fd],
@ -890,25 +892,29 @@ 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.08.0 in unlabeled module, 4.12.0 in labeled *)
@since 4.12.0
@since 4.08.0 *)
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.08.0 in unlabeled module, 4.12.0 in labeled *)
@since 4.12.0
@since 4.08.0 *)
val process_pid : in_channel * out_channel -> int
(** Return the pid of a process opened via {!open_process} or
{!open_process_args}.
@since 4.08.0 in unlabeled module, 4.12.0 in labeled *)
@since 4.12.0
@since 4.08.0 *)
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.08.0 in unlabeled module, 4.12.0 in labeled *)
@since 4.12.0
@since 4.08.0 *)
val close_process_in : in_channel -> process_status
(** Close channels opened by {!open_process_in},
@ -1154,7 +1160,8 @@ val sleepf : float -> unit
(** Stop execution for the given number of seconds. Like [sleep],
but fractions of seconds are supported.
@since 4.03.0 in labeled module, 4.12.0 in unlabeled *)
@since 4.03.0
@since 4.12.0 *)
val times : unit -> process_times
(** Return the execution times of the process.

View File

@ -150,7 +150,8 @@ val unsafe_environment : unit -> string array
privileges. See the documentation for {!unsafe_getenv} for more
details.
@since 4.06.0 in unlabeled module, 4.12.0 in labeled *)
@since 4.12.0
@sinceunlabeled 4.06.0 *)
val getenv : string -> string
(** Return the value associated to a variable in the process
@ -331,7 +332,8 @@ val close : file_descr -> unit
val fsync : file_descr -> unit
(** Flush file buffers to disk.
@since 4.08.0 in unlabeled module, 4.12.0 in labeled *)
@since 4.12.0
@sinceunlabeled 4.08.0 *)
val read : file_descr -> buf:bytes -> pos:int -> len:int -> int
(** [read fd ~buf ~pos ~len] reads [len] bytes from descriptor [fd],
@ -890,25 +892,29 @@ 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.08.0 in unlabeled module, 4.12.0 in labeled *)
@since 4.12.0
@sinceunlabeled 4.08.0 *)
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.08.0 in unlabeled module, 4.12.0 in labeled *)
@since 4.12.0
@sinceunlabeled 4.08.0 *)
val process_pid : in_channel * out_channel -> int
(** Return the pid of a process opened via {!open_process} or
{!open_process_args}.
@since 4.08.0 in unlabeled module, 4.12.0 in labeled *)
@since 4.12.0
@sinceunlabeled 4.08.0 *)
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.08.0 in unlabeled module, 4.12.0 in labeled *)
@since 4.12.0
@sinceunlabeled 4.08.0 *)
val close_process_in : in_channel -> process_status
(** Close channels opened by {!open_process_in},
@ -1154,7 +1160,8 @@ val sleepf : float -> unit
(** Stop execution for the given number of seconds. Like [sleep],
but fractions of seconds are supported.
@since 4.03.0 in labeled module, 4.12.0 in unlabeled *)
@since 4.03.0
@sinceunlabeled 4.12.0 *)
val times : unit -> process_times
(** Return the execution times of the process.

View File

@ -21,7 +21,7 @@
arrayLabels.mli instead.
*)
(** Array operations
(** Array operations.
The labeled version of this module, {!ArrayLabels}, is intended to be used
via {!StdLabels} which replaces {!Array}, {!Bytes}, {!List} and {!String}
@ -157,7 +157,10 @@ val to_list : 'a array -> 'a list
val of_list : 'a list -> 'a array
(** [of_list l] returns a fresh array containing the elements
of [l]. *)
of [l].
@raise Invalid_argument if the length of [l] is greater than
[Sys.max_array_length]. *)
(** {1 Iterators} *)
@ -166,16 +169,16 @@ val iter : ('a -> unit) -> 'a array -> unit
the elements of [a]. It is equivalent to
[f a.(0); f a.(1); ...; f a.(length a - 1); ()]. *)
val map : ('a -> 'b) -> 'a array -> 'b array
(** [map f a] applies function [f] to all the elements of [a],
and builds an array with the results returned by [f]:
[[| f a.(0); f a.(1); ...; f a.(length a - 1) |]]. *)
val iteri : (int -> 'a -> unit) -> 'a array -> unit
(** Same as {!iter}, but the
function is applied to the index of the element as first argument,
and the element itself as second argument. *)
val map : ('a -> 'b) -> 'a array -> 'b array
(** [map f a] applies function [f] to all the elements of [a],
and builds an array with the results returned by [f]:
[[| f a.(0); f a.(1); ...; f a.(length a - 1) |]]. *)
val mapi : (int -> 'a -> 'b) -> 'a array -> 'b array
(** Same as {!map}, but the
function is applied to the index of the element as first argument,
@ -199,14 +202,17 @@ 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 labeled, or 4.03.0 unlabeled *)
@since 4.05.0
@since 4.03.0
*)
val map2 : ('a -> 'b -> 'c) -> 'a array -> 'b array -> 'c array
(** [map2 f a b] applies function [f] to all the elements of [a]
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 labeled, or 4.03.0 unlabeled *)
@since 4.05.0
@since 4.03.0 *)
(** {1 Array scanning} *)

View File

@ -202,14 +202,17 @@ 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 labeled, or 4.03.0 unlabeled *)
@since 4.05.0
@sinceunlabeled 4.03.0
*)
val map2 : f:('a -> 'b -> 'c) -> 'a array -> 'b array -> 'c array
(** [map2 ~f a b] applies function [f] to all the elements of [a]
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 labeled, or 4.03.0 unlabeled *)
@since 4.05.0
@sinceunlabeled 4.03.0 *)
(** {1 Array scanning} *)

View File

@ -124,7 +124,7 @@ val extend : bytes -> int -> int -> bytes
the corresponding side of [s].
@raise Invalid_argument if the result length is negative or
longer than {!Sys.max_string_length} bytes.
@since 4.05.0 in labeled module. *)
@since 4.05.0 in [BytesLabels] *)
val fill : bytes -> int -> int -> char -> unit
(** [fill s pos len c] modifies [s] in place, replacing [len]
@ -153,7 +153,7 @@ val blit_string :
@raise Invalid_argument if [src_pos] and [len] do not
designate a valid range of [src], or if [dst_pos] and [len]
do not designate a valid range of [dst].
@since 4.05.0 in labeled module *)
@since 4.05.0 in [BytesLabels] *)
val concat : bytes -> bytes list -> bytes
(** [concat sep sl] concatenates the list of byte sequences [sl],
@ -165,7 +165,7 @@ val cat : bytes -> bytes -> bytes
as a new byte sequence.
@raise Invalid_argument if the result is longer than
{!Sys.max_string_length} bytes.
@since 4.05.0 in labeled module *)
@since 4.05.0 in [BytesLabels] *)
val iter : (char -> unit) -> bytes -> unit
(** [iter f s] applies function [f] in turn to all the bytes of [s].
@ -294,22 +294,26 @@ 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 in labeled module, 4.03.0 in unlabeled *)
@since 4.05.0
@since 4.03.0 *)
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 in labeled module, 4.03.0 in unlabeled *)
@since 4.05.0
@since 4.03.0 *)
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 in labeled module, 4.03.0 in unlabeled *)
@since 4.05.0
@since 4.03.0 *)
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 in labeled module, 4.03.0 in unlabeled *)
@since 4.05.0
@since 4.03.0 *)
type t = bytes
(** An alias for the type of byte sequences. *)
@ -322,7 +326,8 @@ val compare: t -> t -> int
val equal: t -> t -> bool
(** The equality function for byte sequences.
@since 4.05.0 in labeled module, 4.03.0 in unlabeled *)
@since 4.05.0
@since 4.03.0 *)
(** {1:unsafe Unsafe conversions (for advanced users)}

View File

@ -124,7 +124,7 @@ val extend : bytes -> left:int -> right:int -> bytes
the corresponding side of [s].
@raise Invalid_argument if the result length is negative or
longer than {!Sys.max_string_length} bytes.
@since 4.05.0 in labeled module. *)
@since 4.05.0 in [BytesLabels] *)
val fill : bytes -> pos:int -> len:int -> char -> unit
(** [fill s ~pos ~len c] modifies [s] in place, replacing [len]
@ -153,7 +153,7 @@ val blit_string :
@raise Invalid_argument if [src_pos] and [len] do not
designate a valid range of [src], or if [dst_pos] and [len]
do not designate a valid range of [dst].
@since 4.05.0 in labeled module *)
@since 4.05.0 in [BytesLabels] *)
val concat : sep:bytes -> bytes list -> bytes
(** [concat ~sep sl] concatenates the list of byte sequences [sl],
@ -165,7 +165,7 @@ val cat : bytes -> bytes -> bytes
as a new byte sequence.
@raise Invalid_argument if the result is longer than
{!Sys.max_string_length} bytes.
@since 4.05.0 in labeled module *)
@since 4.05.0 in [BytesLabels] *)
val iter : f:(char -> unit) -> bytes -> unit
(** [iter ~f s] applies function [f] in turn to all the bytes of [s].
@ -294,22 +294,26 @@ 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 in labeled module, 4.03.0 in unlabeled *)
@since 4.05.0
@sinceunlabeled 4.03.0 *)
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 in labeled module, 4.03.0 in unlabeled *)
@since 4.05.0
@sinceunlabeled 4.03.0 *)
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 in labeled module, 4.03.0 in unlabeled *)
@since 4.05.0
@sinceunlabeled 4.03.0 *)
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 in labeled module, 4.03.0 in unlabeled *)
@since 4.05.0
@sinceunlabeled 4.03.0 *)
type t = bytes
(** An alias for the type of byte sequences. *)
@ -322,7 +326,8 @@ val compare: t -> t -> int
val equal: t -> t -> bool
(** The equality function for byte sequences.
@since 4.05.0 in labeled module, 4.03.0 in unlabeled *)
@since 4.05.0
@sinceunlabeled 4.03.0 *)
(** {1:unsafe Unsafe conversions (for advanced users)}

View File

@ -67,7 +67,8 @@ 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 in labeled module or 4.03.0 in unlabeled
@since 4.05.0
@since 4.03.0
*)
val hd : 'a list -> 'a
@ -434,7 +435,8 @@ 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 in labeled module or 4.02.0 in unlabeled module
@since 4.03.0
@since 4.02.0
*)
val merge : ('a -> 'a -> int) -> 'a list -> 'a list -> 'a list

View File

@ -67,7 +67,8 @@ 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 in labeled module or 4.03.0 in unlabeled
@since 4.05.0
@sinceunlabeled 4.03.0
*)
val hd : 'a list -> 'a
@ -434,7 +435,8 @@ 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 in labeled module or 4.02.0 in unlabeled module
@since 4.03.0
@sinceunlabeled 4.02.0
*)
val merge : cmp:('a -> 'a -> int) -> 'a list -> 'a list -> 'a list

View File

@ -294,22 +294,26 @@ 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 in labeled module, 4.03.0 in unlabeled *)
@since 4.05.0
@since 4.03.0 *)
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 in labeled module, 4.03.0 in unlabeled *)
@since 4.05.0
@since 4.03.0 *)
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 in labeled module, 4.03.0 in unlabeled *)
@since 4.05.0
@since 4.03.0 *)
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 in labeled module, 4.03.0 in unlabeled *)
@since 4.05.0
@since 4.03.0 *)
val starts_with :
prefix (* comment thwarts tools/unlabel *) :string -> string -> bool
@ -333,7 +337,8 @@ 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 in labeled module, or 4.04.0 in unlabeled
@since 4.05.0
@since 4.04.0
*)
type t = string
@ -347,7 +352,8 @@ val compare: t -> t -> int
val equal: t -> t -> bool
(** The equal function for strings.
@since 4.05.0 in labeled module, or 4.03.0 in unlabeled *)
@since 4.05.0
@since 4.03.0 *)
(** {1 Iterators} *)

View File

@ -294,22 +294,26 @@ 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 in labeled module, 4.03.0 in unlabeled *)
@since 4.05.0
@sinceunlabeled 4.03.0 *)
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 in labeled module, 4.03.0 in unlabeled *)
@since 4.05.0
@sinceunlabeled 4.03.0 *)
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 in labeled module, 4.03.0 in unlabeled *)
@since 4.05.0
@sinceunlabeled 4.03.0 *)
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 in labeled module, 4.03.0 in unlabeled *)
@since 4.05.0
@sinceunlabeled 4.03.0 *)
val starts_with :
prefix (* comment thwarts tools/unlabel *) :string -> string -> bool
@ -333,7 +337,8 @@ 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 in labeled module, or 4.04.0 in unlabeled
@since 4.05.0
@sinceunlabeled 4.04.0
*)
type t = string
@ -347,7 +352,8 @@ val compare: t -> t -> int
val equal: t -> t -> bool
(** The equal function for strings.
@since 4.05.0 in labeled module, or 4.03.0 in unlabeled *)
@since 4.05.0
@sinceunlabeled 4.03.0 *)
(** {1 Iterators} *)

View File

@ -34,6 +34,9 @@ LABLABREGEX="s/\([a-z_]+:([a-z\('])/\(\1/g"
#OCamldoc code section with ]
TILDEREGEX="s/~([a-z_]*[ \]])/\1/g"
# @sinceunlabeled --> @since
SINCEREGEX="s/sinceunlabeled/since/g"
#Stdlib
perl -p -e "$LABREGEX" stdlib/listLabels.mli > stdlib/list.temp.mli
perl -p -e "$LABREGEX" stdlib/arrayLabels.mli > stdlib/array.temp.mli
@ -41,10 +44,16 @@ perl -p -e "$LABREGEX" stdlib/stringLabels.mli > stdlib/string.temp.mli
perl -p -e "$LABREGEX" stdlib/bytesLabels.mli > stdlib/bytes.temp.mli
#Stdlib tildes
perl -p -e "$TILDEREGEX" stdlib/list.temp.mli > stdlib/list.mli
perl -p -e "$TILDEREGEX" stdlib/array.temp.mli > stdlib/bytes.mli
perl -p -e "$TILDEREGEX" stdlib/string.temp.mli > stdlib/string.mli
perl -p -e "$TILDEREGEX" stdlib/bytes.temp.mli > stdlib/bytes.mli
perl -p -e "$TILDEREGEX" stdlib/list.temp.mli > stdlib/list.2temp.mli
perl -p -e "$TILDEREGEX" stdlib/array.temp.mli > stdlib/array.2temp.mli
perl -p -e "$TILDEREGEX" stdlib/string.temp.mli > stdlib/string.2temp.mli
perl -p -e "$TILDEREGEX" stdlib/bytes.temp.mli > stdlib/bytes.2temp.mli
#Stdlib @since
perl -p -e "$SINCEREGEX" stdlib/list.2temp.mli > stdlib/list.mli
perl -p -e "$SINCEREGEX" stdlib/array.2temp.mli > stdlib/array.mli
perl -p -e "$SINCEREGEX" stdlib/string.2temp.mli > stdlib/string.mli
perl -p -e "$SINCEREGEX" stdlib/bytes.2temp.mli > stdlib/bytes.mli
#MoreLabels
perl -p -e "$LABREGEX" \
@ -65,6 +74,8 @@ perl -p -e "$TILDEREGEX" stdlib/hashtbl.2temp.mli > stdlib/hashtbl.mli
perl -p -e "$TILDEREGEX" stdlib/map.2temp.mli > stdlib/map.mli
perl -p -e "$TILDEREGEX" stdlib/set.2temp.mli > stdlib/set.mli
#(No @since problems in MoreLabels)
#Substitute the labeled modules in to moreLabels.mli
perl -p -e\
's/HASHTBL/`tail -n +19 stdlib\/templates\/hashtbl.template.mli`/e' \
@ -101,7 +112,10 @@ perl -p -e "$LABREGEX" \
otherlibs/unix/unixLabels.mli > otherlibs/unix/unix.temp.mli
#Tildes
perl -p -e "$TILDEREGEX" \
otherlibs/unix/unix.temp.mli > otherlibs/unix/unix.mli
otherlibs/unix/unix.temp.mli > otherlibs/unix/unix.2temp.mli
#Since
perl -p -e "$SINCEREGEX" \
otherlibs/unix/unix.2temp.mli > otherlibs/unix/unix.mli
#Remove type equivalences from unix.mli