Rename tools/unlabel --> tools/sync_stdlib_docs

master
John Whitington 2020-09-10 19:17:43 +01:00
parent 5fd8236343
commit fc101ae849
23 changed files with 81 additions and 73 deletions

View File

@ -14,8 +14,8 @@
(**************************************************************************)
(* NOTE:
If this file is unixLabels.mli, run tools/unlabel after editing it to
generate unix.mli.
If this file is unixLabels.mli, run tools/sync_stdlib_docs after editing it
to generate unix.mli.
If this file is unix.mli, do not edit it directly -- edit
unixLabels.mli instead.
@ -515,7 +515,7 @@ module LargeFile :
val map_file :
file_descr ->
?pos (* thwart tools/unlabel *):int64 ->
?pos (* thwart tools/sync_stdlib_docs *):int64 ->
('a, 'b) Stdlib.Bigarray.kind ->
'c Stdlib.Bigarray.layout -> bool -> int array ->
('a, 'b, 'c) Stdlib.Bigarray.Genarray.t
@ -587,7 +587,7 @@ val rename : string -> string -> unit
owner, etc) of [dst] can either be preserved or be replaced by
those of [src]. *)
val link : ?follow (* thwart tools/unlabel*) :bool ->
val link : ?follow (* thwart tools/sync_stdlib_docs *) :bool ->
string -> string -> unit
(** [link ?follow src dst] creates a hard link named [dst] to the file
named [src].
@ -651,13 +651,14 @@ val access : string -> access_permission list -> unit
(** {1 Operations on file descriptors} *)
val dup : ?cloexec: (* thwart tools/unlabel *) bool -> file_descr -> file_descr
val dup : ?cloexec: (* thwart tools/sync_stdlib_docs *) bool ->
file_descr -> file_descr
(** Return a new file descriptor referencing the same file as
the given descriptor.
See {!set_close_on_exec} for documentation on the [cloexec]
optional argument. *)
val dup2 : ?cloexec: (* thwart tools/unlabel *) bool ->
val dup2 : ?cloexec: (* thwart tools/sync_stdlib_docs *) bool ->
file_descr -> file_descr -> unit
(** [dup2 src dst] duplicates [src] to [dst], closing [dst] if already
opened.
@ -769,7 +770,7 @@ val closedir : dir_handle -> unit
(** {1 Pipes and redirections} *)
val pipe : ?cloexec: (* thwart tools/unlabel *) bool ->
val pipe : ?cloexec: (* thwart tools/sync_stdlib_docs *) bool ->
unit -> file_descr * file_descr
(** Create a pipe. The first component of the result is opened
for reading, that's the exit to the pipe. The second component is
@ -938,7 +939,7 @@ val close_process_full :
(** {1 Symbolic links} *)
val symlink : ?to_dir: (* thwart tools/unlabel*) bool ->
val symlink : ?to_dir: (* thwart tools/sync_stdlib_docs *) bool ->
string -> string -> unit
(** [symlink ?to_dir src dst] creates the file [dst] as a symbolic link
to the file [src]. On Windows, [to_dir] indicates if the symbolic link
@ -1373,7 +1374,7 @@ type sockaddr =
[port] is the port number. *)
val socket :
?cloexec: (* thwart tools/unlabel *) bool ->
?cloexec: (* thwart tools/sync_stdlib_docs *) bool ->
socket_domain -> socket_type -> int -> file_descr
(** Create a new socket in the given domain, and with the
given kind. The third argument is the protocol type; 0 selects
@ -1385,14 +1386,14 @@ val domain_of_sockaddr: sockaddr -> socket_domain
(** Return the socket domain adequate for the given socket address. *)
val socketpair :
?cloexec: (* thwart toosl/unlabel *) bool ->
?cloexec: (* thwart tools/sync_stdlib_docs *) bool ->
socket_domain -> socket_type -> int ->
file_descr * file_descr
(** Create a pair of unnamed sockets, connected together.
See {!set_close_on_exec} for documentation on the [cloexec]
optional argument. *)
val accept : ?cloexec: (* thwart tools/unlabel *) bool ->
val accept : ?cloexec: (* thwart tools/sync_stdlib_docs *) bool ->
file_descr -> file_descr * sockaddr
(** Accept connections on the given socket. The returned descriptor
is a socket connected to the client; the returned address is

View File

@ -14,8 +14,8 @@
(**************************************************************************)
(* NOTE:
If this file is unixLabels.mli, run tools/unlabel after editing it to
generate unix.mli.
If this file is unixLabels.mli, run tools/sync_stdlib_docs after editing it
to generate unix.mli.
If this file is unix.mli, do not edit it directly -- edit
unixLabels.mli instead.
@ -515,7 +515,7 @@ module LargeFile :
val map_file :
file_descr ->
?pos (* thwart tools/unlabel *):int64 ->
?pos (* thwart tools/sync_stdlib_docs *):int64 ->
kind:('a, 'b) Stdlib.Bigarray.kind ->
layout:'c Stdlib.Bigarray.layout -> shared:bool -> dims:int array ->
('a, 'b, 'c) Stdlib.Bigarray.Genarray.t
@ -587,7 +587,7 @@ val rename : src:string -> dst:string -> unit
owner, etc) of [dst] can either be preserved or be replaced by
those of [src]. *)
val link : ?follow (* thwart tools/unlabel*) :bool ->
val link : ?follow (* thwart tools/sync_stdlib_docs *) :bool ->
src:string -> dst:string -> unit
(** [link ?follow ~src ~dst] creates a hard link named [dst] to the file
named [src].
@ -651,13 +651,14 @@ val access : string -> perm:access_permission list -> unit
(** {1 Operations on file descriptors} *)
val dup : ?cloexec: (* thwart tools/unlabel *) bool -> file_descr -> file_descr
val dup : ?cloexec: (* thwart tools/sync_stdlib_docs *) bool ->
file_descr -> file_descr
(** Return a new file descriptor referencing the same file as
the given descriptor.
See {!set_close_on_exec} for documentation on the [cloexec]
optional argument. *)
val dup2 : ?cloexec: (* thwart tools/unlabel *) bool ->
val dup2 : ?cloexec: (* thwart tools/sync_stdlib_docs *) bool ->
src:file_descr -> dst:file_descr -> unit
(** [dup2 ~src ~dst] duplicates [src] to [dst], closing [dst] if already
opened.
@ -769,7 +770,7 @@ val closedir : dir_handle -> unit
(** {1 Pipes and redirections} *)
val pipe : ?cloexec: (* thwart tools/unlabel *) bool ->
val pipe : ?cloexec: (* thwart tools/sync_stdlib_docs *) bool ->
unit -> file_descr * file_descr
(** Create a pipe. The first component of the result is opened
for reading, that's the exit to the pipe. The second component is
@ -938,7 +939,7 @@ val close_process_full :
(** {1 Symbolic links} *)
val symlink : ?to_dir: (* thwart tools/unlabel*) bool ->
val symlink : ?to_dir: (* thwart tools/sync_stdlib_docs *) bool ->
src:string -> dst:string -> unit
(** [symlink ?to_dir ~src ~dst] creates the file [dst] as a symbolic link
to the file [src]. On Windows, [~to_dir] indicates if the symbolic link
@ -1373,7 +1374,7 @@ type sockaddr = Unix.sockaddr =
[port] is the port number. *)
val socket :
?cloexec: (* thwart tools/unlabel *) bool ->
?cloexec: (* thwart tools/sync_stdlib_docs *) bool ->
domain:socket_domain -> kind:socket_type -> protocol:int -> file_descr
(** Create a new socket in the given domain, and with the
given kind. The third argument is the protocol type; 0 selects
@ -1385,14 +1386,14 @@ val domain_of_sockaddr: sockaddr -> socket_domain
(** Return the socket domain adequate for the given socket address. *)
val socketpair :
?cloexec: (* thwart toosl/unlabel *) bool ->
?cloexec: (* thwart tools/sync_stdlib_docs *) bool ->
domain:socket_domain -> kind:socket_type -> protocol:int ->
file_descr * file_descr
(** Create a pair of unnamed sockets, connected together.
See {!set_close_on_exec} for documentation on the [cloexec]
optional argument. *)
val accept : ?cloexec: (* thwart tools/unlabel *) bool ->
val accept : ?cloexec: (* thwart tools/sync_stdlib_docs *) bool ->
file_descr -> file_descr * sockaddr
(** Accept connections on the given socket. The returned descriptor
is a socket connected to the client; the returned address is

View File

@ -14,8 +14,8 @@
(**************************************************************************)
(* NOTE:
If this file is arrayLabels.mli, run tools/unlabel after editing it to
generate array.mli.
If this file is arrayLabels.mli, run tools/sync_stdlib_docs after editing it
to generate array.mli.
If this file is array.mli, do not edit it directly -- edit
arrayLabels.mli instead.

View File

@ -14,8 +14,8 @@
(**************************************************************************)
(* NOTE:
If this file is arrayLabels.mli, run tools/unlabel after editing it to
generate array.mli.
If this file is arrayLabels.mli, run tools/sync_stdlib_docs after editing it
to generate array.mli.
If this file is array.mli, do not edit it directly -- edit
arrayLabels.mli instead.

View File

@ -14,8 +14,8 @@
(**************************************************************************)
(* NOTE:
If this file is bytesLabels.mli, run tools/unlabel after editing it to
generate bytes.mli.
If this file is bytesLabels.mli, run tools/sync_stdlib_docs after editing it
to generate bytes.mli.
If this file is bytes.mli, do not edit it directly -- edit
bytesLabels.mli instead.

View File

@ -14,8 +14,8 @@
(**************************************************************************)
(* NOTE:
If this file is bytesLabels.mli, run tools/unlabel after editing it to
generate bytes.mli.
If this file is bytesLabels.mli, run tools/sync_stdlib_docs after editing it
to generate bytes.mli.
If this file is bytes.mli, do not edit it directly -- edit
bytesLabels.mli instead.

View File

@ -15,8 +15,8 @@
(**************************************************************************)
(* NOTE:
If this file is float.template.mli, run tools/unlabel after editing it to
generate float.mli.
If this file is float.template.mli, run tools/sync_stdlib_docs after editing
it to generate float.mli.
If this file is float.mli, do not edit it directly -- edit
templates/float.template.mli instead.

View File

@ -14,7 +14,7 @@
(**************************************************************************)
(* NOTE: If this file is hashtbl.mli, do not edit it directly! Instead,
edit templates/hashtbl.template.mli and run tools/unlabel *)
edit templates/hashtbl.template.mli and run tools/sync_stdlib_docs *)
(** Hash tables and hash functions.
@ -28,7 +28,8 @@
type (!'a, !'b) t
(** The type of hash tables from type ['a] to type ['b]. *)
val create : ?random: (* thwart tools/unlabel *) bool -> int -> ('a, 'b) t
val create : ?random: (* thwart tools/sync_stdlib_docs *) bool ->
int -> ('a, 'b) t
(** [Hashtbl.create n] creates a new, empty hash table, with
initial size [n]. For best results, [n] should be on the
order of the expected number of elements that will be in
@ -199,7 +200,7 @@ val is_randomized : unit -> bool
by default, [false] otherwise.
@since 4.03.0 *)
val rebuild : ?random (* thwart tools/unlabel *) :bool ->
val rebuild : ?random (* thwart tools/sync_stdlib_docs *) :bool ->
('a, 'b) t -> ('a, 'b) t
(** Return a copy of the given hashtable. Unlike {!copy},
{!rebuild}[ h] re-hashes all the (key, value) entries of
@ -409,7 +410,8 @@ module type SeededS =
sig
type key
type !'a t
val create : ?random (* thwart tools/unlabel *) :bool -> int -> 'a t
val create : ?random (* thwart tools/sync_stdlib_docs *) :bool ->
int -> 'a t
val clear : 'a t -> unit
val reset : 'a t -> unit
val copy : 'a t -> 'a t

View File

@ -14,8 +14,8 @@
(**************************************************************************)
(* NOTE:
If this file is listLabels.mli, run tools/unlabel after editing it to
generate list.mli.
If this file is listLabels.mli, run tools/sync_stdlib_docs after editing it
to generate list.mli.
If this file is list.mli, do not edit it directly -- edit
listLabels.mli instead.

View File

@ -14,8 +14,8 @@
(**************************************************************************)
(* NOTE:
If this file is listLabels.mli, run tools/unlabel after editing it to
generate list.mli.
If this file is listLabels.mli, run tools/sync_stdlib_docs after editing it
to generate list.mli.
If this file is list.mli, do not edit it directly -- edit
listLabels.mli instead.

View File

@ -14,7 +14,7 @@
(**************************************************************************)
(* NOTE: If this file is map.mli, do not edit it directly! Instead,
edit templates/map.template.mli and run tools/unlabel *)
edit templates/map.template.mli and run tools/sync_stdlib_docs *)
(** Association tables over ordered types.

View File

@ -14,7 +14,7 @@
(**************************************************************************)
(* NOTE: Do not edit this file directly. Edit templates/ and run
tools/unlabel *)
tools/sync_stdlib_docs *)
(** Extra labeled libraries.
@ -45,7 +45,8 @@ module Hashtbl : sig
type (!'a, !'b) t = ('a, 'b) Hashtbl.t
(** The type of hash tables from type ['a] to type ['b]. *)
val create : ?random: (* thwart tools/unlabel *) bool -> int -> ('a, 'b) t
val create : ?random: (* thwart tools/sync_stdlib_docs *) bool ->
int -> ('a, 'b) t
(** [Hashtbl.create n] creates a new, empty hash table, with
initial size [n]. For best results, [n] should be on the
order of the expected number of elements that will be in
@ -216,7 +217,7 @@ module Hashtbl : sig
by default, [false] otherwise.
@since 4.03.0 *)
val rebuild : ?random (* thwart tools/unlabel *) :bool ->
val rebuild : ?random (* thwart tools/sync_stdlib_docs *) :bool ->
('a, 'b) t -> ('a, 'b) t
(** Return a copy of the given hashtable. Unlike {!copy},
{!rebuild}[ h] re-hashes all the (key, value) entries of
@ -428,7 +429,8 @@ module Hashtbl : sig
sig
type key
type !'a t
val create : ?random (* thwart tools/unlabel *) :bool -> int -> 'a t
val create : ?random (* thwart tools/sync_stdlib_docs *) :bool ->
int -> 'a t
val clear : 'a t -> unit
val reset : 'a t -> unit
val copy : 'a t -> 'a t

View File

@ -14,7 +14,7 @@
(**************************************************************************)
(* NOTE: If this file is set.mli, do not edit it directly! Instead,
edit templates/set.template.mli and run tools/unlabel *)
edit templates/set.template.mli and run tools/sync_stdlib_docs *)
(** Sets over ordered types.

View File

@ -14,8 +14,8 @@
(**************************************************************************)
(* NOTE:
If this file is stringLabels.mli, run tools/unlabel after editing it to
generate string.mli.
If this file is stringLabels.mli, run tools/sync_stdlib_docs after editing
it to generate string.mli.
If this file is string.mli, do not edit it directly -- edit
stringLabels.mli instead.
@ -320,12 +320,12 @@ val uncapitalize_ascii : string -> string
@since 4.03.0 (4.05.0 in StringLabels) *)
val starts_with :
prefix (* comment thwarts tools/unlabel *) :string -> string -> bool
prefix (* comment thwarts tools/sync_stdlib_docs *) :string -> string -> bool
(** [starts_with ][~][prefix s] tests if [s] starts with [prefix]
@since 4.12.0 *)
val ends_with :
suffix (* comment thwarts tools/unlabel *) :string -> string -> bool
suffix (* comment thwarts tools/sync_stdlib_docs *) :string -> string -> bool
(** [ends_with suffix s] tests if [s] ends with [suffix]
@since 4.12.0 *)

View File

@ -14,8 +14,8 @@
(**************************************************************************)
(* NOTE:
If this file is stringLabels.mli, run tools/unlabel after editing it to
generate string.mli.
If this file is stringLabels.mli, run tools/sync_stdlib_docs after editing
it to generate string.mli.
If this file is string.mli, do not edit it directly -- edit
stringLabels.mli instead.
@ -320,12 +320,12 @@ val uncapitalize_ascii : string -> string
@since 4.03.0 (4.05.0 in StringLabels) *)
val starts_with :
prefix (* comment thwarts tools/unlabel *) :string -> string -> bool
prefix (* comment thwarts tools/sync_stdlib_docs *) :string -> string -> bool
(** [starts_with ][~][prefix s] tests if [s] starts with [prefix]
@since 4.12.0 *)
val ends_with :
suffix (* comment thwarts tools/unlabel *) :string -> string -> bool
suffix (* comment thwarts tools/sync_stdlib_docs *) :string -> string -> bool
(** [ends_with ~suffix s] tests if [s] ends with [suffix]
@since 4.12.0 *)

View File

@ -1,3 +1,3 @@
These templates are fragments of OCaml source files, which tools/unlabel uses
to build the full labeled and unlabeled stdlib modules. At present,
tools/unlabel must be run manually -- it is not a build task.
tools/sync_stdlib_docs must be run manually -- it is not a build task.

View File

@ -15,8 +15,8 @@
(**************************************************************************)
(* NOTE:
If this file is float.template.mli, run tools/unlabel after editing it to
generate float.mli.
If this file is float.template.mli, run tools/sync_stdlib_docs after editing
it to generate float.mli.
If this file is float.mli, do not edit it directly -- edit
templates/float.template.mli instead.

View File

@ -14,7 +14,7 @@
(**************************************************************************)
(* NOTE: If this file is hashtbl.mli, do not edit it directly! Instead,
edit templates/hashtbl.template.mli and run tools/unlabel *)
edit templates/hashtbl.template.mli and run tools/sync_stdlib_docs *)
(** Hash tables and hash functions.
@ -28,7 +28,8 @@
type (!'a, !'b) t
(** The type of hash tables from type ['a] to type ['b]. *)
val create : ?random: (* thwart tools/unlabel *) bool -> int -> ('a, 'b) t
val create : ?random: (* thwart tools/sync_stdlib_docs *) bool ->
int -> ('a, 'b) t
(** [Hashtbl.create n] creates a new, empty hash table, with
initial size [n]. For best results, [n] should be on the
order of the expected number of elements that will be in
@ -199,7 +200,7 @@ val is_randomized : unit -> bool
by default, [false] otherwise.
@since 4.03.0 *)
val rebuild : ?random (* thwart tools/unlabel *) :bool ->
val rebuild : ?random (* thwart tools/sync_stdlib_docs *) :bool ->
('a, 'b) t -> ('a, 'b) t
(** Return a copy of the given hashtable. Unlike {!copy},
{!rebuild}[ h] re-hashes all the (key, value) entries of
@ -409,7 +410,8 @@ module type SeededS =
sig
type key
type !'a t
val create : ?random (* thwart tools/unlabel *) :bool -> int -> 'a t
val create : ?random (* thwart tools/sync_stdlib_docs *) :bool ->
int -> 'a t
val clear : 'a t -> unit
val reset : 'a t -> unit
val copy : 'a t -> 'a t

View File

@ -14,7 +14,7 @@
(**************************************************************************)
(* NOTE: If this file is map.mli, do not edit it directly! Instead,
edit templates/map.template.mli and run tools/unlabel *)
edit templates/map.template.mli and run tools/sync_stdlib_docs *)
(** Association tables over ordered types.

View File

@ -14,7 +14,7 @@
(**************************************************************************)
(* NOTE: Do not edit this file directly. Edit templates/ and run
tools/unlabel *)
tools/sync_stdlib_docs *)
(** Extra labeled libraries.

View File

@ -14,7 +14,7 @@
(**************************************************************************)
(* NOTE: If this file is set.mli, do not edit it directly! Instead,
edit templates/set.template.mli and run tools/unlabel *)
edit templates/set.template.mli and run tools/sync_stdlib_docs *)
(** Sets over ordered types.

View File

@ -78,22 +78,22 @@ case $TRAVIS_EVENT_TYPE in
TRAVIS_MERGE_BASE=$(git merge-base "$TRAVIS_CUR_HEAD" "$TRAVIS_PR_HEAD");;
esac
CheckUnlabel () {
CheckSyncStdlibDocs () {
cat<<EOF
------------------------------------------------------------------------
This test checks that running tools/unlabel is a no-op in the current
state, which means that the labelled/unlabelled .mli files are in sync.
If this check fails, it should be fixable by just running the script and
reviewing the changes it makes.
This test checks that running tools/sync-stdlib-docs is a no-op in the current
state, which means that the labelled/unlabelled .mli files are in sync. If
this check fails, it should be fixable by just running the script and reviewing
the changes it makes.
------------------------------------------------------------------------
EOF
tools/unlabel
tools/sync_stdlib_docs
git diff --quiet --exit-code && result=pass || result=fail
case $result in
pass)
echo "CheckUnlabel: success";;
echo "CheckSyncStdlibDocs: success";;
fail)
echo "CheckUnlabel: failure with the following differences:"
echo "CheckSyncStdlibDocs: failure with the following differences:"
git --no-pager diff
exit 1;;
esac
@ -411,7 +411,7 @@ check-typo)
set +x
CheckTypo;;
check-depend)
CheckUnlabel
CheckSyncStdlibDocs
CheckDepend;;
*) echo unknown CI kind
exit 1