Fix smaller review comments from @dra27

master
John Whitington 2020-07-30 13:26:20 +01:00
parent 85491c8867
commit 0fbeee11be
12 changed files with 165 additions and 142 deletions

View File

@ -140,7 +140,8 @@ val handle_unix_error : ('a -> 'b) -> 'a -> 'b
val environment : unit -> string array
(** Return the process environment, as an array of strings
with the format ``variable=value''. *)
with the format ``variable=value''. The returned array
is empty if the process has special privileges. *)
val unsafe_environment : unit -> string array
(** Return the process environment, as an array of strings with the
@ -199,28 +200,28 @@ type process_status =
type wait_flag =
WNOHANG (** do not block if no child has
died yet, but immediately return with a pid equal to 0.*)
| WUNTRACED (** report also the children that receive stop signals. *)
WNOHANG (** Do not block if no child has
died yet, but immediately return with a pid equal to 0. *)
| WUNTRACED (** Report also the children that receive stop signals. *)
(** Flags for {!waitpid}. *)
val execv : string -> string array -> 'a
(** [execv prog args] execute the program in file [prog], with
the arguments [args], and the current process environment.
These [execv*] functions never return: on success, the current
program is replaced by the new one;
program is replaced by the new one.
@raise Unix_error on failure *)
val execve : string -> string array -> string array -> 'a
(** Same as [execv], except that the third argument provides the
(** Same as {!execv}, except that the third argument provides the
environment to the program executed. *)
val execvp : string -> string array -> 'a
(** Same as [execv], except that
(** Same as {!execv}, except that
the program is searched in the path. *)
val execvpe : string -> string array -> string array -> 'a
(** Same as [execve], except that
(** Same as {!execve}, except that
the program is searched in the path. *)
val fork : unit -> int
@ -236,7 +237,7 @@ val wait : unit -> int * process_status
On Windows: Not implemented, use {!waitpid}. *)
val waitpid : wait_flag list -> int -> int * process_status
(** Same as [wait], but waits for the child process whose pid is given.
(** Same as {!waitpid}, but waits for the child process whose pid is given.
A pid of [-1] means wait for any child.
A pid of [0] means wait for any child in the same process group
as the current process.
@ -328,7 +329,9 @@ val close : file_descr -> unit
(** Close a file descriptor. *)
val fsync : file_descr -> unit
(** Flush file buffers to disk. *)
(** Flush file buffers to disk.
@since 4.08.0 in unlabeled module, 4.12.0 in labeled *)
val read : file_descr -> bytes -> int -> int -> int
(** [read fd buf pos len] reads [len] bytes from descriptor [fd],
@ -343,18 +346,18 @@ val write : file_descr -> bytes -> int -> int -> int
an error occurs. *)
val single_write : file_descr -> bytes -> int -> int -> int
(** Same as [write], but attempts to write only once.
(** Same as {!write}, but attempts to write only once.
Thus, if an error occurs, [single_write] guarantees that no data
has been written. *)
val write_substring : file_descr -> string -> int -> int -> int
(** Same as [write], but take the data from a string instead of a byte
(** Same as {!write}, but take the data from a string instead of a byte
sequence.
@since 4.02.0 *)
val single_write_substring :
file_descr -> string -> int -> int -> int
(** Same as [single_write], but take the data from a string instead of
(** Same as {!single_write}, but take the data from a string instead of
a byte sequence.
@since 4.02.0 *)
@ -511,7 +514,6 @@ module LargeFile :
regular integers (type [int]), thus allowing operating on files
whose sizes are greater than [max_int]. *)
(** {1 Mapping files into memory} *)
val map_file :
@ -623,11 +625,12 @@ val fchmod : file_descr -> file_perm -> unit
On Windows: not implemented. *)
val chown : string -> int -> int -> unit
(** Change the owner uid and owner gid of the named file. *)
(** Change the owner uid and owner gid of the named file.
On Windows: not implemented. *)
val fchown : file_descr -> int -> int -> unit
(** Change the owner uid and owner gid of the named file.
On Windows: not implemented (make no sense on a DOS file system). *)
(** Change the owner uid and owner gid of an opened file.
On Windows: not implemented. *)
val umask : int -> int
(** Set the process's file mode creation mask, and return the previous
@ -636,10 +639,12 @@ val umask : int -> int
val access : string -> access_permission list -> unit
(** Check that the process has the given permissions over the named file.
@raise Unix_error otherwise.
On Windows, execute permission [X_OK], cannot be tested, it just
tests for read permission instead. *)
tests for read permission instead.
@raise Unix_error otherwise.
*)
(** {1 Operations on file descriptors} *)
@ -816,13 +821,13 @@ val open_process_in : string -> in_channel
more efficient alternative to {!open_process_in}. *)
val open_process_out : string -> out_channel
(** same as {!open_process_in}, but redirect the standard input of
the command to a pipe. data written to the returned output channel
(** Same as {!open_process_in}, but redirect the standard input of
the command to a pipe. Data written to the returned output channel
is sent to the standard input of the command.
warning: writes on output channels are buffered, hence be careful
to call {!stdlib.flush} at the right times to ensure
Warning: writes on output channels are buffered, hence be careful
to call {!Stdlib.flush} at the right times to ensure
correct synchronization.
if the command does not need to be run through the shell,
If the command does not need to be run through the shell,
{!open_process_args_out} can be used instead of
{!open_process_out}. *)
@ -993,7 +998,6 @@ val select :
(** {1 Locking} *)
type lock_command =
F_ULOCK (** Unlock a region *)
| F_LOCK (** Lock a region for writing, and block if already locked *)
@ -1336,8 +1340,8 @@ type socket_domain =
| PF_INET (** Internet domain (IPv4) *)
| PF_INET6 (** Internet domain (IPv6) *)
(** The type of socket domains. Not all platforms support
IPv6 sockets (type [PF_INET6]). Windows does not support
[PF_UNIX]. *)
IPv6 sockets (type [PF_INET6]). On Windows, [PF_UNIX]
is not implemented. *)
type socket_type =
SOCK_STREAM (** Stream socket *)
@ -1380,7 +1384,9 @@ val accept : ?cloexec: (* thwart tools/unlabel *) 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
the address of the connecting client. *)
the address of the connecting client.
See {!set_close_on_exec} for documentation on the [cloexec]
optional argument. *)
val bind : file_descr -> sockaddr -> unit
(** Bind a socket to an address. *)
@ -1416,8 +1422,7 @@ type msg_flag =
MSG_OOB
| MSG_DONTROUTE
| MSG_PEEK (**)
(** The flags for {!recv}, {!recvfrom},
{!send} and {!sendto}. *)
(** The flags for {!recv}, {!recvfrom}, {!send} and {!sendto}. *)
val recv :
file_descr -> bytes -> int -> int -> msg_flag list -> int
@ -1552,12 +1557,13 @@ val establish_server :
The function given as first argument is called for each connection
with two buffered channels connected to the client. A new process
is created for each connection. The function {!establish_server}
never returns normally. *)
never returns normally.
On Windows, it is not implemented. Use threads. *)
(** {1 Host and protocol databases} *)
type host_entry =
{ h_name : string;
h_aliases : string array;
@ -1586,27 +1592,27 @@ val gethostname : unit -> string
val gethostbyname : string -> host_entry
(** Find an entry in [hosts] with the given name.
@raise Not_found if no such entry exist. *)
@raise Not_found if no such entry exists. *)
val gethostbyaddr : inet_addr -> host_entry
(** Find an entry in [hosts] with the given address.
@raise Not_found if no such entry exist. *)
@raise Not_found if no such entry exists. *)
val getprotobyname : string -> protocol_entry
(** Find an entry in [protocols] with the given name.
@raise Not_found if no such entry exist. *)
@raise Not_found if no such entry exists. *)
val getprotobynumber : int -> protocol_entry
(** Find an entry in [protocols] with the given protocol number.
@raise Not_found if no such entry exist. *)
@raise Not_found if no such entry exists. *)
val getservbyname : string -> string -> service_entry
(** Find an entry in [services] with the given name.
@raise Not_found if no such entry exist. *)
@raise Not_found if no such entry exists. *)
val getservbyport : int -> string -> service_entry
(** Find an entry in [services] with the given service number.
@raise Not_found if no such entry exist. *)
@raise Not_found if no such entry exists. *)
type addr_info =
{ ai_family : socket_domain; (** Socket domain *)
@ -1729,7 +1735,9 @@ type terminal_io =
val tcgetattr : file_descr -> terminal_io
(** Return the status of the terminal referred to by the given
file descriptor. *)
file descriptor.
On Windows, not implemented.*)
type setattr_when =
TCSANOW
@ -1744,7 +1752,9 @@ val tcsetattr : file_descr -> setattr_when -> terminal_io -> unit
or after flushing all input that has been received but not
read ([TCSAFLUSH]). [TCSADRAIN] is recommended when changing
the output parameters; [TCSAFLUSH], when changing the input
parameters. *)
parameters.
On Windows, not implemented. *)
val tcsendbreak : file_descr -> int -> unit
(** Send a break condition on the given file descriptor.
@ -1769,7 +1779,9 @@ val tcflush : file_descr -> flush_queue -> unit
transmitted, or data received but not yet read, depending on the
second argument: [TCIFLUSH] flushes data received but not read,
[TCOFLUSH] flushes data written but not transmitted, and
[TCIOFLUSH] flushes both. *)
[TCIOFLUSH] flushes both.
On Windows, not implemented. *)
type flow_action =
TCOOFF

View File

@ -140,7 +140,8 @@ val handle_unix_error : ('a -> 'b) -> 'a -> 'b
val environment : unit -> string array
(** Return the process environment, as an array of strings
with the format ``variable=value''. *)
with the format ``variable=value''. The returned array
is empty if the process has special privileges. *)
val unsafe_environment : unit -> string array
(** Return the process environment, as an array of strings with the
@ -199,28 +200,28 @@ type process_status = Unix.process_status =
type wait_flag = Unix.wait_flag =
WNOHANG (** do not block if no child has
died yet, but immediately return with a pid equal to 0.*)
| WUNTRACED (** report also the children that receive stop signals. *)
WNOHANG (** Do not block if no child has
died yet, but immediately return with a pid equal to 0. *)
| WUNTRACED (** Report also the children that receive stop signals. *)
(** Flags for {!waitpid}. *)
val execv : prog:string -> args:string array -> 'a
(** [execv ~prog ~args] execute the program in file [prog], with
the arguments [args], and the current process environment.
These [execv*] functions never return: on success, the current
program is replaced by the new one;
program is replaced by the new one.
@raise Unix_error on failure *)
val execve : prog:string -> args:string array -> env:string array -> 'a
(** Same as [execv], except that the third argument provides the
(** Same as {!execv}, except that the third argument provides the
environment to the program executed. *)
val execvp : prog:string -> args:string array -> 'a
(** Same as [execv], except that
(** Same as {!execv}, except that
the program is searched in the path. *)
val execvpe : prog:string -> args:string array -> env:string array -> 'a
(** Same as [execve], except that
(** Same as {!execve}, except that
the program is searched in the path. *)
val fork : unit -> int
@ -236,7 +237,7 @@ val wait : unit -> int * process_status
On Windows: Not implemented, use {!waitpid}. *)
val waitpid : mode:wait_flag list -> int -> int * process_status
(** Same as [wait], but waits for the child process whose pid is given.
(** Same as {!waitpid}, but waits for the child process whose pid is given.
A pid of [-1] means wait for any child.
A pid of [0] means wait for any child in the same process group
as the current process.
@ -328,7 +329,9 @@ val close : file_descr -> unit
(** Close a file descriptor. *)
val fsync : file_descr -> unit
(** Flush file buffers to disk. *)
(** Flush file buffers to disk.
@since 4.08.0 in unlabeled module, 4.12.0 in labeled *)
val read : file_descr -> buf:bytes -> pos:int -> len:int -> int
(** [read fd ~buf ~pos ~len] reads [len] bytes from descriptor [fd],
@ -343,18 +346,18 @@ val write : file_descr -> buf:bytes -> pos:int -> len:int -> int
an error occurs. *)
val single_write : file_descr -> buf:bytes -> pos:int -> len:int -> int
(** Same as [write], but attempts to write only once.
(** Same as {!write}, but attempts to write only once.
Thus, if an error occurs, [single_write] guarantees that no data
has been written. *)
val write_substring : file_descr -> buf:string -> pos:int -> len:int -> int
(** Same as [write], but take the data from a string instead of a byte
(** Same as {!write}, but take the data from a string instead of a byte
sequence.
@since 4.02.0 *)
val single_write_substring :
file_descr -> buf:string -> pos:int -> len:int -> int
(** Same as [single_write], but take the data from a string instead of
(** Same as {!single_write}, but take the data from a string instead of
a byte sequence.
@since 4.02.0 *)
@ -511,7 +514,6 @@ module LargeFile :
regular integers (type [int]), thus allowing operating on files
whose sizes are greater than [max_int]. *)
(** {1 Mapping files into memory} *)
val map_file :
@ -623,11 +625,12 @@ val fchmod : file_descr -> perm:file_perm -> unit
On Windows: not implemented. *)
val chown : string -> uid:int -> gid:int -> unit
(** Change the owner uid and owner gid of the named file. *)
(** Change the owner uid and owner gid of the named file.
On Windows: not implemented. *)
val fchown : file_descr -> uid:int -> gid:int -> unit
(** Change the owner uid and owner gid of the named file.
On Windows: not implemented (make no sense on a DOS file system). *)
(** Change the owner uid and owner gid of an opened file.
On Windows: not implemented. *)
val umask : int -> int
(** Set the process's file mode creation mask, and return the previous
@ -636,10 +639,12 @@ val umask : int -> int
val access : string -> perm:access_permission list -> unit
(** Check that the process has the given permissions over the named file.
@raise Unix_error otherwise.
On Windows, execute permission [X_OK], cannot be tested, it just
tests for read permission instead. *)
tests for read permission instead.
@raise Unix_error otherwise.
*)
(** {1 Operations on file descriptors} *)
@ -816,13 +821,13 @@ val open_process_in : string -> in_channel
more efficient alternative to {!open_process_in}. *)
val open_process_out : string -> out_channel
(** same as {!open_process_in}, but redirect the standard input of
the command to a pipe. data written to the returned output channel
(** Same as {!open_process_in}, but redirect the standard input of
the command to a pipe. Data written to the returned output channel
is sent to the standard input of the command.
warning: writes on output channels are buffered, hence be careful
to call {!stdlib.flush} at the right times to ensure
Warning: writes on output channels are buffered, hence be careful
to call {!Stdlib.flush} at the right times to ensure
correct synchronization.
if the command does not need to be run through the shell,
If the command does not need to be run through the shell,
{!open_process_args_out} can be used instead of
{!open_process_out}. *)
@ -993,7 +998,6 @@ val select :
(** {1 Locking} *)
type lock_command = Unix.lock_command =
F_ULOCK (** Unlock a region *)
| F_LOCK (** Lock a region for writing, and block if already locked *)
@ -1336,8 +1340,8 @@ type socket_domain = Unix.socket_domain =
| PF_INET (** Internet domain (IPv4) *)
| PF_INET6 (** Internet domain (IPv6) *)
(** The type of socket domains. Not all platforms support
IPv6 sockets (type [PF_INET6]). Windows does not support
[PF_UNIX]. *)
IPv6 sockets (type [PF_INET6]). On Windows, [PF_UNIX]
is not implemented. *)
type socket_type = Unix.socket_type =
SOCK_STREAM (** Stream socket *)
@ -1380,7 +1384,9 @@ val accept : ?cloexec: (* thwart tools/unlabel *) 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
the address of the connecting client. *)
the address of the connecting client.
See {!set_close_on_exec} for documentation on the [cloexec]
optional argument. *)
val bind : file_descr -> addr:sockaddr -> unit
(** Bind a socket to an address. *)
@ -1416,8 +1422,7 @@ type msg_flag = Unix.msg_flag =
MSG_OOB
| MSG_DONTROUTE
| MSG_PEEK (**)
(** The flags for {!recv}, {!recvfrom},
{!send} and {!sendto}. *)
(** The flags for {!recv}, {!recvfrom}, {!send} and {!sendto}. *)
val recv :
file_descr -> buf:bytes -> pos:int -> len:int -> mode:msg_flag list -> int
@ -1552,12 +1557,13 @@ val establish_server :
The function given as first argument is called for each connection
with two buffered channels connected to the client. A new process
is created for each connection. The function {!establish_server}
never returns normally. *)
never returns normally.
On Windows, it is not implemented. Use threads. *)
(** {1 Host and protocol databases} *)
type host_entry = Unix.host_entry =
{ h_name : string;
h_aliases : string array;
@ -1586,27 +1592,27 @@ val gethostname : unit -> string
val gethostbyname : string -> host_entry
(** Find an entry in [hosts] with the given name.
@raise Not_found if no such entry exist. *)
@raise Not_found if no such entry exists. *)
val gethostbyaddr : inet_addr -> host_entry
(** Find an entry in [hosts] with the given address.
@raise Not_found if no such entry exist. *)
@raise Not_found if no such entry exists. *)
val getprotobyname : string -> protocol_entry
(** Find an entry in [protocols] with the given name.
@raise Not_found if no such entry exist. *)
@raise Not_found if no such entry exists. *)
val getprotobynumber : int -> protocol_entry
(** Find an entry in [protocols] with the given protocol number.
@raise Not_found if no such entry exist. *)
@raise Not_found if no such entry exists. *)
val getservbyname : string -> protocol:string -> service_entry
(** Find an entry in [services] with the given name.
@raise Not_found if no such entry exist. *)
@raise Not_found if no such entry exists. *)
val getservbyport : int -> protocol:string -> service_entry
(** Find an entry in [services] with the given service number.
@raise Not_found if no such entry exist. *)
@raise Not_found if no such entry exists. *)
type addr_info = Unix.addr_info =
{ ai_family : socket_domain; (** Socket domain *)
@ -1729,7 +1735,9 @@ type terminal_io = Unix.terminal_io =
val tcgetattr : file_descr -> terminal_io
(** Return the status of the terminal referred to by the given
file descriptor. *)
file descriptor.
On Windows, not implemented.*)
type setattr_when = Unix.setattr_when =
TCSANOW
@ -1744,7 +1752,9 @@ val tcsetattr : file_descr -> mode:setattr_when -> terminal_io -> unit
or after flushing all input that has been received but not
read ([TCSAFLUSH]). [TCSADRAIN] is recommended when changing
the output parameters; [TCSAFLUSH], when changing the input
parameters. *)
parameters.
On Windows, not implemented. *)
val tcsendbreak : file_descr -> duration:int -> unit
(** Send a break condition on the given file descriptor.
@ -1769,7 +1779,9 @@ val tcflush : file_descr -> mode:flush_queue -> unit
transmitted, or data received but not yet read, depending on the
second argument: [TCIFLUSH] flushes data received but not read,
[TCOFLUSH] flushes data written but not transmitted, and
[TCIOFLUSH] flushes both. *)
[TCIOFLUSH] flushes both.
On Windows, not implemented. *)
type flow_action = Unix.flow_action =
TCOOFF

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 : f:('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 : f:('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 : f:(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 : f:('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 : f:(int -> 'a -> 'b) -> 'a array -> 'b array
(** Same as {!map}, but the
function is applied to the index of the element as first argument,

View File

@ -47,8 +47,6 @@
Bytes are represented by the OCaml type [char].
The labeled version of this module, {!BytesLabels}, is intended to be used
through {!StdLabels} which replaces {!Array}, {!Bytes}, {!List} and
{!String} with their labeled counterparts.
@ -116,7 +114,7 @@ val sub : bytes -> int -> int -> bytes
valid range of [s]. *)
val sub_string : bytes -> int -> int -> string
(** Same as [sub] but return a string instead of a byte sequence. *)
(** Same as {!sub} but return a string instead of a byte sequence. *)
val extend : bytes -> int -> int -> bytes
(** [extend s left right] returns a new byte sequence that contains
@ -126,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 *)
@since 4.05.0 in labeled module. *)
val fill : bytes -> int -> int -> char -> unit
(** [fill s pos len c] modifies [s] in place, replacing [len]
@ -155,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 *)
@since 4.05.0 in labeled module *)
val concat : bytes -> bytes list -> bytes
(** [concat sep sl] concatenates the list of byte sequences [sl],
@ -164,10 +162,10 @@ val concat : bytes -> bytes list -> bytes
val cat : bytes -> bytes -> bytes
(** [cat s1 s2] concatenates [s1] and [s2] and returns the result
as new byte sequence.
as a new byte sequence.
@raise Invalid_argument if the result is longer than
{!Sys.max_string_length} bytes.
@since 4.05.0 *)
@since 4.05.0 in labeled module *)
val iter : (char -> unit) -> bytes -> unit
(** [iter f s] applies function [f] in turn to all the bytes of [s].
@ -175,14 +173,14 @@ val iter : (char -> unit) -> bytes -> unit
(length s - 1)); ()]. *)
val iteri : (int -> char -> unit) -> bytes -> unit
(** Same as [iter], but the function is applied to the index of
(** Same as {!iter}, but the function is applied to the index of
the byte as first argument and the byte itself as second
argument. *)
val map : (char -> char) -> bytes -> bytes
(** [map f s] applies function [f] in turn to all the bytes of [s] and
stores the resulting bytes in a new sequence that is returned as
the result. *)
(** [map f s] applies function [f] in turn to all the bytes of [s] (in
increasing index order) and stores the resulting bytes in a new sequence
that is returned as the result. *)
val mapi : (int -> char -> char) -> bytes -> bytes
(** [mapi f s] calls [f] with each character of [s] and its
@ -230,7 +228,7 @@ val index_from : bytes -> int -> char -> int
@raise Not_found if [c] does not occur in [s] after position [i]. *)
val index_from_opt: bytes -> int -> char -> int option
(** [index_from _opts i c] returns the index of the first occurrence of
(** [index_from_opt s i c] returns the index of the first occurrence of
byte [c] in [s] after position [i] or [None] if [c] does not occur in [s]
after position [i].
[index_opt s c] is equivalent to [index_from_opt s 0 c].

View File

@ -47,8 +47,6 @@
Bytes are represented by the OCaml type [char].
The labeled version of this module, {!BytesLabels}, is intended to be used
through {!StdLabels} which replaces {!Array}, {!Bytes}, {!List} and
{!String} with their labeled counterparts.
@ -116,7 +114,7 @@ val sub : bytes -> pos:int -> len:int -> bytes
valid range of [s]. *)
val sub_string : bytes -> pos:int -> len:int -> string
(** Same as [sub] but return a string instead of a byte sequence. *)
(** Same as {!sub} but return a string instead of a byte sequence. *)
val extend : bytes -> left:int -> right:int -> bytes
(** [extend s ~left ~right] returns a new byte sequence that contains
@ -126,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 *)
@since 4.05.0 in labeled module. *)
val fill : bytes -> pos:int -> len:int -> char -> unit
(** [fill s ~pos ~len c] modifies [s] in place, replacing [len]
@ -155,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 *)
@since 4.05.0 in labeled module *)
val concat : sep:bytes -> bytes list -> bytes
(** [concat ~sep sl] concatenates the list of byte sequences [sl],
@ -164,10 +162,10 @@ val concat : sep:bytes -> bytes list -> bytes
val cat : bytes -> bytes -> bytes
(** [cat s1 s2] concatenates [s1] and [s2] and returns the result
as new byte sequence.
as a new byte sequence.
@raise Invalid_argument if the result is longer than
{!Sys.max_string_length} bytes.
@since 4.05.0 *)
@since 4.05.0 in labeled module *)
val iter : f:(char -> unit) -> bytes -> unit
(** [iter ~f s] applies function [f] in turn to all the bytes of [s].
@ -175,14 +173,14 @@ val iter : f:(char -> unit) -> bytes -> unit
(length s - 1)); ()]. *)
val iteri : f:(int -> char -> unit) -> bytes -> unit
(** Same as [iter], but the function is applied to the index of
(** Same as {!iter}, but the function is applied to the index of
the byte as first argument and the byte itself as second
argument. *)
val map : f:(char -> char) -> bytes -> bytes
(** [map ~f s] applies function [f] in turn to all the bytes of [s] and
stores the resulting bytes in a new sequence that is returned as
the result. *)
(** [map ~f s] applies function [f] in turn to all the bytes of [s] (in
increasing index order) and stores the resulting bytes in a new sequence
that is returned as the result. *)
val mapi : f:(int -> char -> char) -> bytes -> bytes
(** [mapi ~f s] calls [f] with each character of [s] and its
@ -230,7 +228,7 @@ val index_from : bytes -> int -> char -> int
@raise Not_found if [c] does not occur in [s] after position [i]. *)
val index_from_opt: bytes -> int -> char -> int option
(** [index_from _opts i c] returns the index of the first occurrence of
(** [index_from_opt s i c] returns the index of the first occurrence of
byte [c] in [s] after position [i] or [None] if [c] does not occur in [s]
after position [i].
[index_opt s c] is equivalent to [index_from_opt s 0 c].

View File

@ -195,7 +195,7 @@ val randomize : unit -> unit
val is_randomized : unit -> bool
(** Return [true] if the tables are currently created in randomized mode
by default, [false] otherwise.
by default, [false] otherwise.
@since 4.03.0 *)
val rebuild : ?random (* thwart tools/unlabel *) :bool ->

View File

@ -46,7 +46,7 @@
*)
type 'a t = 'a list = [] | (::) of 'a * 'a list (**)
(** An alias for the type of lists. *)
(** An alias for the type of lists. *)
val length : 'a list -> int
(** Return the length (number of elements) of the given list. *)
@ -96,7 +96,7 @@ val nth_opt : 'a list -> int -> 'a option
*)
val rev : 'a list -> 'a list
(** List reversal. *)
(** List reversal. *)
val init : int -> (int -> 'a) -> 'a list
(** [init len f] is [f 0; f 1; ...; f (len-1)], evaluated left to right.

View File

@ -46,7 +46,7 @@
*)
type 'a t = 'a list = [] | (::) of 'a * 'a list (**)
(** An alias for the type of lists. *)
(** An alias for the type of lists. *)
val length : 'a list -> int
(** Return the length (number of elements) of the given list. *)
@ -96,7 +96,7 @@ val nth_opt : 'a list -> int -> 'a option
*)
val rev : 'a list -> 'a list
(** List reversal. *)
(** List reversal. *)
val init : len:int -> f:(int -> 'a) -> 'a list
(** [init ~len ~f] is [f 0; f 1; ...; f (len-1)], evaluated left to right.

View File

@ -46,11 +46,11 @@ val create : ?random: (* thwart tools/unlabel *) bool -> int -> ('a, 'b) t
the table. The table grows as needed, so [n] is just an
initial guess.
The optional [random] parameter (a boolean) controls whether
The optional [~random] parameter (a boolean) controls whether
the internal organization of the hash table is randomized at each
execution of [Hashtbl.create] or deterministic over all executions.
A hash table that is created with [random] set to [false] uses a
A hash table that is created with [~random] set to [false] uses a
fixed hash function ({!hash}) to distribute keys among
buckets. As a consequence, collisions between keys happen
deterministically. In Web-facing applications or other
@ -59,7 +59,7 @@ val create : ?random: (* thwart tools/unlabel *) bool -> int -> ('a, 'b) t
denial-of-service attack: the attacker sends input crafted to
create many collisions in the table, slowing the application down.
A hash table that is created with [random] set to [true] uses the seeded
A hash table that is created with [~random] set to [true] uses the seeded
hash function {!seeded_hash} with a seed that is randomly chosen at hash
table creation time. In effect, the hash function used is randomly selected
among [2^{30}] different hash functions. All these hash functions have
@ -69,7 +69,7 @@ val create : ?random: (* thwart tools/unlabel *) bool -> int -> ('a, 'b) t
deterministic: elements are enumerated in different orders at different runs
of the program.
If no [random] parameter is given, hash tables are created
If no [~random] parameter is given, hash tables are created
in non-random mode by default. This default can be changed
either programmatically by calling {!randomize} or by
setting the [R] flag in the [OCAMLRUNPARAM] environment variable.
@ -206,7 +206,7 @@ val randomize : unit -> unit
val is_randomized : unit -> bool
(** Return [true] if the tables are currently created in randomized mode
by default, [false] otherwise.
by default, [false] otherwise.
@since 4.03.0 *)
val rebuild : ?random (* thwart tools/unlabel *) :bool ->

View File

@ -154,8 +154,8 @@ val iteri : (int -> char -> unit) -> string -> unit
val map : (char -> char) -> string -> string
(** [map f s] applies function [f] in turn to all
the characters of [s] and stores the results in a new string that
is returned.
the characters of [s] (in increasing index order)
and stores the results in a new string that is returned.
@since 4.00.0 *)
val mapi : (int -> char -> char) -> string -> string
@ -167,7 +167,7 @@ val mapi : (int -> char -> char) -> string -> string
val trim : string -> string
(** Return a copy of the argument, without leading and trailing
whitespace. The characters regarded as whitespace are: [' '],
['\012'], ['\n'], ['\r'], and ['\t']. If there is no leading nor
['\012'], ['\n'], ['\r'], and ['\t']. If there is neither leading nor
trailing whitespace character in the argument, return the original
string itself, not a copy.
@since 4.00.0 *)
@ -205,9 +205,9 @@ val rindex : string -> char -> int
@raise Not_found if [c] does not occur in [s]. *)
val rindex_opt: string -> char -> int option
(** [index_opt s c] returns the index of the first
occurrence of character [c] in string [s], or
[None] if [c] does not occur in [s].
(** [String.rindex_opt s c] returns the index of the last occurrence
of character [c] in string [s], or [None] if [c] does not occur in
[s].
@since 4.05 *)
val index_from : string -> int -> char -> int
@ -347,7 +347,7 @@ val compare: t -> t -> int
val equal: t -> t -> bool
(** The equal function for strings.
@since 4.05.0 in labeled module, or 4.30.0 in unlabeled *)
@since 4.05.0 in labeled module, or 4.03.0 in unlabeled *)
(** {1 Iterators} *)

View File

@ -154,8 +154,8 @@ val iteri : f:(int -> char -> unit) -> string -> unit
val map : f:(char -> char) -> string -> string
(** [map ~f s] applies function [f] in turn to all
the characters of [s] and stores the results in a new string that
is returned.
the characters of [s] (in increasing index order)
and stores the results in a new string that is returned.
@since 4.00.0 *)
val mapi : f:(int -> char -> char) -> string -> string
@ -167,7 +167,7 @@ val mapi : f:(int -> char -> char) -> string -> string
val trim : string -> string
(** Return a copy of the argument, without leading and trailing
whitespace. The characters regarded as whitespace are: [' '],
['\012'], ['\n'], ['\r'], and ['\t']. If there is no leading nor
['\012'], ['\n'], ['\r'], and ['\t']. If there is neither leading nor
trailing whitespace character in the argument, return the original
string itself, not a copy.
@since 4.00.0 *)
@ -205,9 +205,9 @@ val rindex : string -> char -> int
@raise Not_found if [c] does not occur in [s]. *)
val rindex_opt: string -> char -> int option
(** [index_opt s c] returns the index of the first
occurrence of character [c] in string [s], or
[None] if [c] does not occur in [s].
(** [String.rindex_opt s c] returns the index of the last occurrence
of character [c] in string [s], or [None] if [c] does not occur in
[s].
@since 4.05 *)
val index_from : string -> int -> char -> int
@ -347,7 +347,7 @@ val compare: t -> t -> int
val equal: t -> t -> bool
(** The equal function for strings.
@since 4.05.0 in labeled module, or 4.30.0 in unlabeled *)
@since 4.05.0 in labeled module, or 4.03.0 in unlabeled *)
(** {1 Iterators} *)

View File

@ -35,11 +35,11 @@ val create : ?random: (* thwart tools/unlabel *) bool -> int -> ('a, 'b) t
the table. The table grows as needed, so [n] is just an
initial guess.
The optional [random] parameter (a boolean) controls whether
The optional [~random] parameter (a boolean) controls whether
the internal organization of the hash table is randomized at each
execution of [Hashtbl.create] or deterministic over all executions.
A hash table that is created with [random] set to [false] uses a
A hash table that is created with [~random] set to [false] uses a
fixed hash function ({!hash}) to distribute keys among
buckets. As a consequence, collisions between keys happen
deterministically. In Web-facing applications or other
@ -48,7 +48,7 @@ val create : ?random: (* thwart tools/unlabel *) bool -> int -> ('a, 'b) t
denial-of-service attack: the attacker sends input crafted to
create many collisions in the table, slowing the application down.
A hash table that is created with [random] set to [true] uses the seeded
A hash table that is created with [~random] set to [true] uses the seeded
hash function {!seeded_hash} with a seed that is randomly chosen at hash
table creation time. In effect, the hash function used is randomly selected
among [2^{30}] different hash functions. All these hash functions have
@ -58,7 +58,7 @@ val create : ?random: (* thwart tools/unlabel *) bool -> int -> ('a, 'b) t
deterministic: elements are enumerated in different orders at different runs
of the program.
If no [random] parameter is given, hash tables are created
If no [~random] parameter is given, hash tables are created
in non-random mode by default. This default can be changed
either programmatically by calling {!randomize} or by
setting the [R] flag in the [OCAMLRUNPARAM] environment variable.
@ -195,7 +195,7 @@ val randomize : unit -> unit
val is_randomized : unit -> bool
(** Return [true] if the tables are currently created in randomized mode
by default, [false] otherwise.
by default, [false] otherwise.
@since 4.03.0 *)
val rebuild : ?random (* thwart tools/unlabel *) :bool ->