Tildes back in labeled modules

master
John Whitington 2020-07-29 14:58:01 +01:00
parent dd1f3789f2
commit 85491c8867
12 changed files with 151 additions and 151 deletions

View File

@ -797,7 +797,7 @@ val create_process :
val create_process_env :
string -> string array -> string array -> file_descr ->
file_descr -> file_descr -> int
(** [create_process_env prog args env new_stdin new_stdout new_stderr]
(** [create_process_env prog args env stdin stdout stderr]
works as {!create_process}, except that the extra argument
[env] specifies the environment passed to the program. *)
@ -933,11 +933,11 @@ val close_process_full :
val symlink : ?to_dir: (* thwart tools/unlabel*) 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
to the file [src]. On Windows, [to_dir] indicates if the symbolic link
points to a directory or a file; if omitted, [symlink] examines [src]
using [stat] and picks appropriately, if [src] does not exist then [false]
is assumed (for this reason, it is recommended that the [~to_dir] parameter
be specified in new code). On Unix, [~to_dir] is ignored.
is assumed (for this reason, it is recommended that the [to_dir] parameter
be specified in new code). On Unix, [to_dir] is ignored.
Windows symbolic links are available in Windows Vista onwards. There are some
important differences between Windows symlinks and their POSIX counterparts.

View File

@ -205,7 +205,7 @@ type wait_flag = Unix.wait_flag =
(** Flags for {!waitpid}. *)
val execv : prog:string -> args:string array -> 'a
(** [execv prog args] execute the program in file [prog], with
(** [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;
@ -331,12 +331,12 @@ val fsync : file_descr -> unit
(** Flush file buffers to disk. *)
val read : file_descr -> buf:bytes -> pos:int -> len:int -> int
(** [read fd buf pos len] reads [len] bytes from descriptor [fd],
(** [read fd ~buf ~pos ~len] reads [len] bytes from descriptor [fd],
storing them in byte sequence [buf], starting at position [pos] in
[buf]. Return the number of bytes actually read. *)
val write : file_descr -> buf:bytes -> pos:int -> len:int -> int
(** [write fd buf pos len] writes [len] bytes to descriptor [fd],
(** [write fd ~buf ~pos ~len] writes [len] bytes to descriptor [fd],
taking them from byte sequence [buf], starting at position [pos]
in [buff]. Return the number of bytes actually written. [write]
repeats the writing operation until all bytes have been written or
@ -521,7 +521,7 @@ val map_file :
layout:'c Stdlib.Bigarray.layout -> shared:bool -> dims:int array ->
('a, 'b, 'c) Stdlib.Bigarray.Genarray.t
(** Memory mapping of a file as a Bigarray.
[map_file fd kind layout shared dims]
[map_file fd ~kind ~layout ~shared ~dims]
returns a Bigarray of kind [kind], layout [layout],
and dimensions as specified in [dims]. The data contained in
this Bigarray are the contents of the file referred to by
@ -581,7 +581,7 @@ val unlink : string -> unit
*)
val rename : src:string -> dst:string -> unit
(** [rename src dst] changes the name of a file from [src] to [dst],
(** [rename ~src ~dst] changes the name of a file from [src] to [dst],
moving it between directories if needed. If [dst] already
exists, its contents will be replaced with those of [src].
Depending on the operating system, the metadata (permissions,
@ -590,7 +590,7 @@ val rename : src:string -> dst:string -> unit
val link : ?follow (* thwart tools/unlabel*) :bool ->
src:string -> dst:string -> unit
(** [link ?follow src dst] creates a hard link named [dst] to the file
(** [link ?follow ~src ~dst] creates a hard link named [dst] to the file
named [src].
@param follow indicates whether a [src] symlink is followed or a
@ -653,7 +653,7 @@ val dup : ?cloexec: (* thwart tools/unlabel *) bool -> file_descr -> file_descr
val dup2 : ?cloexec: (* thwart tools/unlabel *) bool ->
src:file_descr -> dst:file_descr -> unit
(** [dup2 src dst] duplicates [src] to [dst], closing [dst] if already
(** [dup2 ~src ~dst] duplicates [src] to [dst], closing [dst] if already
opened.
See {!set_close_on_exec} for documentation on the [cloexec]
optional argument. *)
@ -781,7 +781,7 @@ val mkfifo : string -> perm:file_perm -> unit
val create_process :
prog:string -> args:string array -> stdin:file_descr -> stdout:file_descr ->
stderr:file_descr -> int
(** [create_process prog args stdin stdout stderr]
(** [create_process ~prog ~args ~stdin ~stdout ~stderr]
forks a new process that executes the program
in file [prog], with arguments [args]. The pid of the new
process is returned immediately; the new process executes
@ -797,7 +797,7 @@ val create_process :
val create_process_env :
prog:string -> args:string array -> env:string array -> stdin:file_descr ->
stdout:file_descr -> stderr:file_descr -> int
(** [create_process_env prog args env new_stdin new_stdout new_stderr]
(** [create_process_env ~prog ~args ~env ~stdin ~stdout ~stderr]
works as {!create_process}, except that the extra argument
[env] specifies the environment passed to the program. *)
@ -932,7 +932,7 @@ val close_process_full :
val symlink : ?to_dir: (* thwart tools/unlabel*) bool ->
src:string -> dst:string -> unit
(** [symlink ?to_dir src dst] creates the file [dst] as a symbolic link
(** [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
points to a directory or a file; if omitted, [symlink] examines [src]
using [stat] and picks appropriately, if [src] does not exist then [false]
@ -1004,7 +1004,7 @@ type lock_command = Unix.lock_command =
(** Commands for {!lockf}. *)
val lockf : file_descr -> mode:lock_command -> len:int -> unit
(** [lockf fd mode len] puts a lock on a region of the file opened
(** [lockf fd ~mode ~len] puts a lock on a region of the file opened
as [fd]. The region starts at the current read/write position for
[fd] (as set by {!lseek}), and extends [len] bytes forward if
[len] is positive, [len] bytes backwards if [len] is negative,
@ -1042,7 +1042,7 @@ val lockf : file_descr -> mode:lock_command -> len:int -> unit
*)
val kill : pid:int -> signal:int -> unit
(** [kill pid signal] sends signal number [signal] to the process
(** [kill ~pid ~signal] sends signal number [signal] to the process
with id [pid]. On Windows, only the {!Sys.sigkill} signal
is emulated. *)
@ -1052,7 +1052,7 @@ type sigprocmask_command = Unix.sigprocmask_command =
| SIG_UNBLOCK
val sigprocmask : mode:sigprocmask_command -> int list -> int list
(** [sigprocmask mode sigs] changes the set of blocked signals.
(** [sigprocmask ~mode sigs] changes the set of blocked signals.
If [mode] is [SIG_SETMASK], blocked signals are set to those in
the list [sigs].
If [mode] is [SIG_BLOCK], the signals in [sigs] are added to

View File

@ -84,9 +84,9 @@ val make_float: int -> float array
(** @deprecated [make_float] is an alias for {!create_float}. *)
val init : int -> f:(int -> 'a) -> 'a array
(** [init n f] returns a fresh array of length [n],
(** [init n ~f] returns a fresh array of length [n],
with element number [i] initialized to the result of [f i].
In other terms, [init n f] tabulates the results of [f]
In other terms, [init n ~f] tabulates the results of [f]
applied to the integers [0] to [n-1].
@raise Invalid_argument if [n < 0] or [n > Sys.max_array_length].
@ -94,7 +94,7 @@ val init : int -> f:(int -> 'a) -> 'a array
size is only [Sys.max_array_length / 2].*)
val make_matrix : dimx:int -> dimy:int -> 'a -> 'a array array
(** [make_matrix dimx dimy e] returns a two-dimensional array
(** [make_matrix ~dimx ~dimy e] returns a two-dimensional array
(an array of arrays) with first dimension [dimx] and
second dimension [dimy]. All the elements of this new matrix
are initially physically equal to [e].
@ -120,7 +120,7 @@ val concat : 'a array list -> 'a array
(** Same as {!append}, but concatenates a list of arrays. *)
val sub : 'a array -> pos:int -> len:int -> 'a array
(** [sub a pos len] returns a fresh array of length [len],
(** [sub a ~pos ~len] returns a fresh array of length [len],
containing the elements number [pos] to [pos + len - 1]
of array [a].
@ -133,7 +133,7 @@ val copy : 'a array -> 'a array
containing the same elements as [a]. *)
val fill : 'a array -> pos:int -> len:int -> 'a -> unit
(** [fill a pos len x] modifies the array [a] in place,
(** [fill a ~pos ~len x] modifies the array [a] in place,
storing [x] in elements number [pos] to [pos + len - 1].
@raise Invalid_argument if [pos] and [len] do not
@ -142,7 +142,7 @@ val fill : 'a array -> pos:int -> len:int -> 'a -> unit
val blit :
src:'a array -> src_pos:int -> dst:'a array -> dst_pos:int -> len:int ->
unit
(** [blit src src_pos dst dst_pos len] copies [len] elements
(** [blit ~src ~src_pos ~dst ~dst_pos ~len] copies [len] elements
from array [src], starting at element number [src_pos], to array [dst],
starting at element number [dst_pos]. It works correctly even if
[src] and [dst] are the same array, and the source and
@ -162,12 +162,12 @@ val of_list : 'a list -> 'a array
(** {1 Iterators} *)
val iter : f:('a -> unit) -> 'a array -> unit
(** [iter f a] applies function [f] in turn to all
(** [iter ~f a] applies function [f] in turn to all
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],
(** [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) |]]. *)
@ -182,12 +182,12 @@ val mapi : f:(int -> 'a -> 'b) -> 'a array -> 'b array
and the element itself as second argument. *)
val fold_left : f:('a -> 'b -> 'a) -> init:'a -> 'b array -> 'a
(** [fold_left f init a] computes
(** [fold_left ~f ~init a] computes
[f (... (f (f init a.(0)) a.(1)) ...) a.(n-1)],
where [n] is the length of the array [a]. *)
val fold_right : f:('b -> 'a -> 'a) -> 'b array -> init:'a -> 'a
(** [fold_right f a init] computes
(** [fold_right ~f a ~init] computes
[f a.(0) (f a.(1) ( ... (f a.(n-1) init) ...))],
where [n] is the length of the array [a]. *)
@ -196,13 +196,13 @@ val fold_right : f:('b -> 'a -> 'a) -> 'b array -> init:'a -> 'a
val iter2 : f:('a -> 'b -> unit) -> 'a array -> 'b array -> unit
(** [iter2 f a b] applies function [f] to all the elements of [a]
(** [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 *)
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]
(** [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.
@ -212,13 +212,13 @@ val map2 : f:('a -> 'b -> 'c) -> 'a array -> 'b array -> 'c array
(** {1 Array scanning} *)
val for_all : f:('a -> bool) -> 'a array -> bool
(** [for_all f [|a1; ...; an|]] checks if all elements
(** [for_all ~f [|a1; ...; an|]] checks if all elements
of the array satisfy the predicate [f]. That is, it returns
[(f a1) && (f a2) && ... && (f an)].
@since 4.03.0 *)
val exists : f:('a -> bool) -> 'a array -> bool
(** [exists f [|a1; ...; an|]] checks if at least one element of
(** [exists ~f [|a1; ...; an|]] checks if at least one element of
the array satisfies the predicate [f]. That is, it returns
[(f a1) || (f a2) || ... || (f an)].
@since 4.03.0 *)
@ -234,7 +234,7 @@ val exists2 : f:('a -> 'b -> bool) -> 'a array -> 'b array -> bool
@since 4.11.0 *)
val mem : 'a -> set:'a array -> bool
(** [mem a set] is true if and only if [a] is structurally equal
(** [mem a ~set] is true if and only if [a] is structurally equal
to an element of [l] (i.e. there is an [x] in [l] such that
[compare a x = 0]).
@since 4.03.0 *)

View File

@ -109,7 +109,7 @@ val to_string : bytes -> string
sequence. *)
val sub : bytes -> pos:int -> len:int -> bytes
(** [sub s pos len] returns a new byte sequence of length [len],
(** [sub s ~pos ~len] returns a new byte sequence of length [len],
containing the subsequence of [s] that starts at position [pos]
and has length [len].
@raise Invalid_argument if [pos] and [len] do not designate a
@ -119,7 +119,7 @@ val sub_string : bytes -> pos:int -> len:int -> string
(** 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
(** [extend s ~left ~right] returns a new byte sequence that contains
the bytes of [s], with [left] uninitialized bytes prepended and
[right] uninitialized bytes appended to it. If [left] or [right]
is negative, then bytes are removed (instead of appended) from
@ -129,7 +129,7 @@ val extend : bytes -> left:int -> right:int -> bytes
@since 4.05.0 *)
val fill : bytes -> pos:int -> len:int -> char -> unit
(** [fill s pos len c] modifies [s] in place, replacing [len]
(** [fill s ~pos ~len c] modifies [s] in place, replacing [len]
characters with [c], starting at [pos].
@raise Invalid_argument if [pos] and [len] do not designate a
valid range of [s]. *)
@ -137,7 +137,7 @@ val fill : bytes -> pos:int -> len:int -> char -> unit
val blit :
src:bytes -> src_pos:int -> dst:bytes -> dst_pos:int -> len:int
-> unit
(** [blit src src_pos dst dst_pos len] copies [len] bytes from sequence
(** [blit ~src ~src_pos ~dst ~dst_pos ~len] copies [len] bytes from sequence
[src], starting at index [src_pos], to sequence [dst], starting at
index [dst_pos]. It works correctly even if [src] and [dst] are the
same byte sequence, and the source and destination intervals
@ -149,7 +149,7 @@ val blit :
val blit_string :
src:string -> src_pos:int -> dst:bytes -> dst_pos:int -> len:int
-> unit
(** [blit src src_pos dst dst_pos len] copies [len] bytes from string
(** [blit ~src ~src_pos ~dst ~dst_pos ~len] copies [len] bytes from string
[src], starting at index [src_pos], to byte sequence [dst],
starting at index [dst_pos].
@raise Invalid_argument if [src_pos] and [len] do not
@ -158,7 +158,7 @@ val blit_string :
@since 4.05.0 *)
val concat : sep:bytes -> bytes list -> bytes
(** [concat sep sl] concatenates the list of byte sequences [sl],
(** [concat ~sep sl] concatenates the list of byte sequences [sl],
inserting the separator byte sequence [sep] between each, and
returns the result as a new byte sequence. *)
@ -170,7 +170,7 @@ val cat : bytes -> bytes -> bytes
@since 4.05.0 *)
val iter : f:(char -> unit) -> bytes -> unit
(** [iter f s] applies function [f] in turn to all the bytes of [s].
(** [iter ~f s] applies function [f] in turn to all the bytes of [s].
It is equivalent to [f (get s 0); f (get s 1); ...; f (get s
(length s - 1)); ()]. *)
@ -180,12 +180,12 @@ val iteri : f:(int -> char -> unit) -> bytes -> unit
argument. *)
val map : f:(char -> char) -> bytes -> bytes
(** [map f s] applies function [f] in turn to all the bytes of [s] and
(** [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. *)
val mapi : f:(int -> char -> char) -> bytes -> bytes
(** [mapi f s] calls [f] with each character of [s] and its
(** [mapi ~f s] calls [f] with each character of [s] and its
index (in increasing index order) and stores the resulting bytes
in a new sequence that is returned as the result. *)

View File

@ -185,13 +185,13 @@ val fold_left_map :
*)
val fold_left : ('a -> 'b -> 'a) -> 'a -> 'b list -> 'a
(** [fold_left f a [b1; ...; bn]] is
[f (... (f (f a b1) b2) ...) bn].
(** [fold_left f init [b1; ...; bn]] is
[f (... (f (f init b1) b2) ...) bn].
*)
val fold_right : ('a -> 'b -> 'b) -> 'a list -> 'b -> 'b
(** [fold_right f [a1; ...; an] b] is
[f a1 (f a2 (... (f an b) ...))]. Not tail-recursive.
(** [fold_right f [a1; ...; an] init] is
[f a1 (f a2 (... (f an init) ...))]. Not tail-recursive.
*)

View File

@ -99,7 +99,7 @@ val rev : 'a list -> 'a list
(** 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.
(** [init ~len ~f] is [f 0; f 1; ...; f (len-1)], evaluated left to right.
@raise Invalid_argument if [len < 0].
@since 4.06.0
*)
@ -133,7 +133,7 @@ val flatten : 'a list list -> 'a list
val iter : f:('a -> unit) -> 'a list -> unit
(** [iter f [a1; ...; an]] applies function [f] in turn to
(** [iter ~f [a1; ...; an]] applies function [f] in turn to
[a1; ...; an]. It is equivalent to
[begin f a1; f a2; ...; f an; () end].
*)
@ -146,7 +146,7 @@ val iteri : f:(int -> 'a -> unit) -> 'a list -> unit
*)
val map : f:('a -> 'b) -> 'a list -> 'b list
(** [map f [a1; ...; an]] applies function [f] to [a1, ..., an],
(** [map ~f [a1; ...; an]] applies function [f] to [a1, ..., an],
and builds the list [[f a1; ...; f an]]
with the results returned by [f]. Not tail-recursive.
*)
@ -159,20 +159,20 @@ val mapi : f:(int -> 'a -> 'b) -> 'a list -> 'b list
*)
val rev_map : f:('a -> 'b) -> 'a list -> 'b list
(** [rev_map f l] gives the same result as
(** [rev_map ~f l] gives the same result as
{!rev}[ (]{!map}[ f l)], but is tail-recursive and
more efficient.
*)
val filter_map : f:('a -> 'b option) -> 'a list -> 'b list
(** [filter_map f l] applies [f] to every element of [l], filters
(** [filter_map ~f l] applies [f] to every element of [l], filters
out the [None] elements and returns the list of the arguments of
the [Some] elements.
@since 4.08.0
*)
val concat_map : f:('a -> 'b list) -> 'a list -> 'b list
(** [concat_map f l] gives the same result as
(** [concat_map ~f l] gives the same result as
{!concat}[ (]{!map}[ f l)]. Tail-recursive.
@since 4.10.0
*)
@ -185,13 +185,13 @@ val fold_left_map :
*)
val fold_left : f:('a -> 'b -> 'a) -> init:'a -> 'b list -> 'a
(** [fold_left f a [b1; ...; bn]] is
[f (... (f (f a b1) b2) ...) bn].
(** [fold_left ~f ~init [b1; ...; bn]] is
[f (... (f (f init b1) b2) ...) bn].
*)
val fold_right : f:('a -> 'b -> 'b) -> 'a list -> init:'b -> 'b
(** [fold_right f [a1; ...; an] b] is
[f a1 (f a2 (... (f an b) ...))]. Not tail-recursive.
(** [fold_right ~f [a1; ...; an] ~init] is
[f a1 (f a2 (... (f an init) ...))]. Not tail-recursive.
*)
@ -199,28 +199,28 @@ val fold_right : f:('a -> 'b -> 'b) -> 'a list -> init:'b -> 'b
val iter2 : f:('a -> 'b -> unit) -> 'a list -> 'b list -> unit
(** [iter2 f [a1; ...; an] [b1; ...; bn]] calls in turn
(** [iter2 ~f [a1; ...; an] [b1; ...; bn]] calls in turn
[f a1 b1; ...; f an bn].
@raise Invalid_argument if the two lists are determined
to have different lengths.
*)
val map2 : f:('a -> 'b -> 'c) -> 'a list -> 'b list -> 'c list
(** [map2 f [a1; ...; an] [b1; ...; bn]] is
(** [map2 ~f [a1; ...; an] [b1; ...; bn]] is
[[f a1 b1; ...; f an bn]].
@raise Invalid_argument if the two lists are determined
to have different lengths. Not tail-recursive.
*)
val rev_map2 : f:('a -> 'b -> 'c) -> 'a list -> 'b list -> 'c list
(** [rev_map2 f l1 l2] gives the same result as
(** [rev_map2 ~f l1 l2] gives the same result as
{!rev}[ (]{!map2}[ f l1 l2)], but is tail-recursive and
more efficient.
*)
val fold_left2 :
f:('a -> 'b -> 'c -> 'a) -> init:'a -> 'b list -> 'c list -> 'a
(** [fold_left2 f init [a1; ...; an] [b1; ...; bn]] is
(** [fold_left2 ~f ~init [a1; ...; an] [b1; ...; bn]] is
[f (... (f (f init a1 b1) a2 b2) ...) an bn].
@raise Invalid_argument if the two lists are determined
to have different lengths.
@ -228,7 +228,7 @@ val fold_left2 :
val fold_right2 :
f:('a -> 'b -> 'c -> 'c) -> 'a list -> 'b list -> init:'c -> 'c
(** [fold_right2 f [a1; ...; an] [b1; ...; bn] init] is
(** [fold_right2 ~f [a1; ...; an] [b1; ...; bn] ~init] is
[f a1 b1 (f a2 b2 (... (f an bn init) ...))].
@raise Invalid_argument if the two lists are determined
to have different lengths. Not tail-recursive.
@ -239,14 +239,14 @@ val fold_right2 :
val for_all : f:('a -> bool) -> 'a list -> bool
(** [for_all f [a1; ...; an]] checks if all elements of the list
(** [for_all ~f [a1; ...; an]] checks if all elements of the list
satisfy the predicate [f]. That is, it returns
[(f a1) && (f a2) && ... && (f an)] for a non-empty list and
[true] if the list is empty.
*)
val exists : f:('a -> bool) -> 'a list -> bool
(** [exists f [a1; ...; an]] checks if at least one element of
(** [exists ~f [a1; ...; an]] checks if at least one element of
the list satisfies the predicate [f]. That is, it returns
[(f a1) || (f a2) || ... || (f an)] for a non-empty list and
[false] if the list is empty.
@ -265,7 +265,7 @@ val exists2 : f:('a -> 'b -> bool) -> 'a list -> 'b list -> bool
*)
val mem : 'a -> set:'a list -> bool
(** [mem a set] is true if and only if [a] is equal
(** [mem a ~set] is true if and only if [a] is equal
to an element of [set].
*)
@ -279,14 +279,14 @@ val memq : 'a -> set:'a list -> bool
val find : f:('a -> bool) -> 'a list -> 'a
(** [find f l] returns the first element of the list [l]
(** [find ~f l] returns the first element of the list [l]
that satisfies the predicate [f].
@raise Not_found if there is no value that satisfies [f] in the
list [l].
*)
val find_opt : f:('a -> bool) -> 'a list -> 'a option
(** [find f l] returns the first element of the list [l]
(** [find ~f l] returns the first element of the list [l]
that satisfies the predicate [f].
Returns [None] if there is no value that satisfies [f] in the
list [l].
@ -294,14 +294,14 @@ val find_opt : f:('a -> bool) -> 'a list -> 'a option
*)
val find_map : f:('a -> 'b option) -> 'a list -> 'b option
(** [find_map f l] applies [f] to the elements of [l] in order,
(** [find_map ~f l] applies [f] to the elements of [l] in order,
and returns the first result of the form [Some v], or [None]
if none exist.
@since 4.10.0
*)
val filter : f:('a -> bool) -> 'a list -> 'a list
(** [filter f l] returns all the elements of the list [l]
(** [filter ~f l] returns all the elements of the list [l]
that satisfy the predicate [f]. The order of the elements
in the input list is preserved.
*)
@ -318,7 +318,7 @@ val filteri : f:(int -> 'a -> bool) -> 'a list -> 'a list
*)
val partition : f:('a -> bool) -> 'a list -> 'a list * 'a list
(** [partition f l] returns a pair of lists [(l1, l2)], where
(** [partition ~f l] returns a pair of lists [(l1, l2)], where
[l1] is the list of all the elements of [l] that
satisfy the predicate [f], and [l2] is the list of all the
elements of [l] that do not satisfy [f].
@ -440,7 +440,7 @@ val sort_uniq : cmp:('a -> 'a -> int) -> 'a list -> 'a list
val merge : cmp:('a -> 'a -> int) -> 'a list -> 'a list -> 'a list
(** Merge two lists:
Assuming that [l1] and [l2] are sorted according to the
comparison function [cmp], [merge cmp l1 l2] will return a
comparison function [cmp], [merge ~cmp l1 l2] will return a
sorted list containing all the elements of [l1] and [l2].
If several elements compare equal, the elements of [l1] will be
before the elements of [l2].

View File

@ -90,7 +90,7 @@ val copy : ('a, 'b) t -> ('a, 'b) t
(** Return a copy of the given hashtable. *)
val add : ('a, 'b) t -> key:'a -> data:'b -> unit
(** [Hashtbl.add tbl key data] adds a binding of [key] to [data]
(** [Hashtbl.add tbl ~key ~data] adds a binding of [key] to [data]
in table [tbl].
Previous bindings for [key] are not removed, but simply
hidden. That is, after performing {!remove}[ tbl key],
@ -121,14 +121,14 @@ val remove : ('a, 'b) t -> 'a -> unit
It does nothing if [x] is not bound in [tbl]. *)
val replace : ('a, 'b) t -> key:'a -> data:'b -> unit
(** [Hashtbl.replace tbl key data] replaces the current binding of [key]
(** [Hashtbl.replace tbl ~key ~data] replaces the current binding of [key]
in [tbl] by a binding of [key] to [data]. If [key] is unbound in [tbl],
a binding of [key] to [data] is added to [tbl].
This is functionally equivalent to {!remove}[ tbl key]
followed by {!add}[ tbl key data]. *)
val iter : f:(key:'a -> data:'b -> unit) -> ('a, 'b) t -> unit
(** [Hashtbl.iter f tbl] applies [f] to all bindings in table [tbl].
(** [Hashtbl.iter ~f tbl] applies [f] to all bindings in table [tbl].
[f] receives the key as first argument, and the associated value
as second argument. Each binding is presented exactly once to [f].
@ -148,7 +148,7 @@ val iter : f:(key:'a -> data:'b -> unit) -> ('a, 'b) t -> unit
*)
val filter_map_inplace: f:(key:'a -> data:'b -> 'b option) -> ('a, 'b) t -> unit
(** [Hashtbl.filter_map_inplace f tbl] applies [f] to all bindings in
(** [Hashtbl.filter_map_inplace ~f tbl] applies [f] to all bindings in
table [tbl] and update each binding depending on the result of
[f]. If [f] returns [None], the binding is discarded. If it
returns [Some new_val], the binding is update to associate the key
@ -158,7 +158,7 @@ val filter_map_inplace: f:(key:'a -> data:'b -> 'b option) -> ('a, 'b) t -> unit
@since 4.03.0 *)
val fold : f:(key:'a -> data:'b -> 'c -> 'c) -> ('a, 'b) t -> init:'c -> 'c
(** [Hashtbl.fold f tbl init] computes
(** [Hashtbl.fold ~f tbl ~init] computes
[(f kN dN ... (f k1 d1 init)...)],
where [k1 ... kN] are the keys of all bindings in [tbl],
and [d1 ... dN] are the associated values.
@ -585,7 +585,7 @@ module type S =
and [false] otherwise. *)
val add: key:key -> data:'a -> 'a t -> 'a t
(** [add key data m] returns a map containing the same bindings as
(** [add ~key ~data m] returns a map containing the same bindings as
[m], plus a binding of [key] to [data]. If [key] was already bound
in [m] to a value that is physically equal to [data],
[m] is returned unchanged (the result of the function is
@ -594,7 +594,7 @@ module type S =
@before 4.03 Physical equality was not ensured. *)
val update: key:key -> f:('a option -> 'a option) -> 'a t -> 'a t
(** [update key f m] returns a map containing the same bindings as
(** [update ~key ~f m] returns a map containing the same bindings as
[m], except for the binding of [key]. Depending on the value of
[y] where [y] is [f (find_opt key m)], the binding of [key] is
added, removed or updated. If [y] is [None], the binding is
@ -621,7 +621,7 @@ module type S =
val merge:
f:(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
(** [merge f m1 m2] computes a map whose keys are a subset of the keys of
(** [merge ~f m1 m2] computes a map whose keys are a subset of the keys of
[m1] and of [m2]. The presence of each such binding, and the
corresponding value, is determined with the function [f].
In terms of the [find_opt] operation, we have
@ -631,7 +631,7 @@ module type S =
*)
val union: f:(key -> 'a -> 'a -> 'a option) -> 'a t -> 'a t -> 'a t
(** [union f m1 m2] computes a map whose keys are a subset of the keys
(** [union ~f m1 m2] computes a map whose keys are a subset of the keys
of [m1] and of [m2]. When the same binding is defined in both
arguments, the function [f] is used to combine them.
This is a special case of [merge]: [union f m1 m2] is equivalent
@ -649,36 +649,36 @@ module type S =
used to compare data associated with equal keys in the two maps. *)
val equal: cmp:('a -> 'a -> bool) -> 'a t -> 'a t -> bool
(** [equal cmp m1 m2] tests whether the maps [m1] and [m2] are
(** [equal ~cmp m1 m2] tests whether the maps [m1] and [m2] are
equal, that is, contain equal keys and associate them with
equal data. [cmp] is the equality predicate used to compare
the data associated with the keys. *)
val iter: f:(key:key -> data:'a -> unit) -> 'a t -> unit
(** [iter f m] applies [f] to all bindings in map [m].
(** [iter ~f m] applies [f] to all bindings in map [m].
[f] receives the key as first argument, and the associated value
as second argument. The bindings are passed to [f] in increasing
order with respect to the ordering over the type of the keys. *)
val fold: f:(key:key -> data:'a -> 'b -> 'b) -> 'a t -> init:'b -> 'b
(** [fold f m init] computes [(f kN dN ... (f k1 d1 init)...)],
(** [fold ~f m ~init] computes [(f kN dN ... (f k1 d1 init)...)],
where [k1 ... kN] are the keys of all bindings in [m]
(in increasing order), and [d1 ... dN] are the associated data. *)
val for_all: f:(key -> 'a -> bool) -> 'a t -> bool
(** [for_all f m] checks if all the bindings of the map
(** [for_all ~f m] checks if all the bindings of the map
satisfy the predicate [f].
@since 3.12.0
*)
val exists: f:(key -> 'a -> bool) -> 'a t -> bool
(** [exists f m] checks if at least one binding of the map
(** [exists ~f m] checks if at least one binding of the map
satisfies the predicate [f].
@since 3.12.0
*)
val filter: f:(key -> 'a -> bool) -> 'a t -> 'a t
(** [filter f m] returns the map with all the bindings in [m]
(** [filter ~f m] returns the map with all the bindings in [m]
that satisfy predicate [p]. If every binding in [m] satisfies [f],
[m] is returned unchanged (the result of the function is then
physically equal to [m])
@ -687,7 +687,7 @@ module type S =
*)
val filter_map: f:(key -> 'a -> 'b option) -> 'a t -> 'b t
(** [filter_map f m] applies the function [f] to every binding of
(** [filter_map ~f m] applies the function [f] to every binding of
[m], and builds a map from the results. For each binding
[(k, v)] in the input map:
- if [f k v] is [None] then [k] is not in the result,
@ -707,7 +707,7 @@ module type S =
*)
val partition: f:(key -> 'a -> bool) -> 'a t -> 'a t * 'a t
(** [partition f m] returns a pair of maps [(m1, m2)], where
(** [partition ~f m] returns a pair of maps [(m1, m2)], where
[m1] contains all the bindings of [m] that satisfy the
predicate [f], and [m2] is the map with all the bindings of
[m] that do not satisfy [f].
@ -789,7 +789,7 @@ module type S =
*)
val find_first: f:(key -> bool) -> 'a t -> key * 'a
(** [find_first f m], where [f] is a monotonically increasing function,
(** [find_first ~f m], where [f] is a monotonically increasing function,
returns the binding of [m] with the lowest key [k] such that [f k],
or raises [Not_found] if no such key exists.
@ -802,28 +802,28 @@ module type S =
*)
val find_first_opt: f:(key -> bool) -> 'a t -> (key * 'a) option
(** [find_first_opt f m], where [f] is a monotonically increasing function,
(** [find_first_opt ~f m], where [f] is a monotonically increasing function,
returns an option containing the binding of [m] with the lowest key [k]
such that [f k], or [None] if no such key exists.
@since 4.05
*)
val find_last: f:(key -> bool) -> 'a t -> key * 'a
(** [find_last f m], where [f] is a monotonically decreasing function,
(** [find_last ~f m], where [f] is a monotonically decreasing function,
returns the binding of [m] with the highest key [k] such that [f k],
or raises [Not_found] if no such key exists.
@since 4.05
*)
val find_last_opt: f:(key -> bool) -> 'a t -> (key * 'a) option
(** [find_last_opt f m], where [f] is a monotonically decreasing function,
(** [find_last_opt ~f m], where [f] is a monotonically decreasing function,
returns an option containing the binding of [m] with the highest key [k]
such that [f k], or [None] if no such key exists.
@since 4.05
*)
val map: f:('a -> 'b) -> 'a t -> 'b t
(** [map f m] returns a map with same domain as [m], where the
(** [map ~f m] returns a map with same domain as [m], where the
associated value [a] of all bindings of [m] has been
replaced by the result of the application of [f] to [a].
The bindings are passed to [f] in increasing order
@ -973,12 +973,12 @@ module type S =
the set [s2]. *)
val iter: f:(elt -> unit) -> t -> unit
(** [iter f s] applies [f] in turn to all elements of [s].
(** [iter ~f s] applies [f] in turn to all elements of [s].
The elements of [s] are presented to [f] in increasing order
with respect to the ordering over the type of the elements. *)
val map: f:(elt -> elt) -> t -> t
(** [map f s] is the set whose elements are [f a0],[f a1]... [f
(** [map ~f s] is the set whose elements are [f a0],[f a1]... [f
aN], where [a0],[a1]...[aN] are the elements of [s].
The elements are passed to [f] in increasing order
@ -990,26 +990,26 @@ module type S =
@since 4.04.0 *)
val fold: f:(elt -> 'a -> 'a) -> t -> init:'a -> 'a
(** [fold f s init] computes [(f xN ... (f x2 (f x1 init))...)],
(** [fold ~f s init] computes [(f xN ... (f x2 (f x1 init))...)],
where [x1 ... xN] are the elements of [s], in increasing order. *)
val for_all: f:(elt -> bool) -> t -> bool
(** [for_all f s] checks if all elements of the set
(** [for_all ~f s] checks if all elements of the set
satisfy the predicate [f]. *)
val exists: f:(elt -> bool) -> t -> bool
(** [exists f s] checks if at least one element of
(** [exists ~f s] checks if at least one element of
the set satisfies the predicate [f]. *)
val filter: f:(elt -> bool) -> t -> t
(** [filter f s] returns the set of all elements in [s]
(** [filter ~f s] returns the set of all elements in [s]
that satisfy predicate [f]. If [f] satisfies every element in [s],
[s] is returned unchanged (the result of the function is then
physically equal to [s]).
@before 4.03 Physical equality was not ensured.*)
val filter_map: f:(elt -> elt option) -> t -> t
(** [filter_map f s] returns the set of all [v] such that
(** [filter_map ~f s] returns the set of all [v] such that
[f x = Some v] for some element [x] of [s].
For example,
@ -1025,7 +1025,7 @@ module type S =
*)
val partition: f:(elt -> bool) -> t -> t * t
(** [partition f s] returns a pair of sets [(s1, s2)], where
(** [partition ~f s] returns a pair of sets [(s1, s2)], where
[s1] is the set of all the elements of [s] that satisfy the
predicate [f], and [s2] is the set of all the elements of
[s] that do not satisfy [f]. *)
@ -1095,7 +1095,7 @@ module type S =
@since 4.05 *)
val find_first: f:(elt -> bool) -> t -> elt
(** [find_first f s], where [f] is a monotonically increasing function,
(** [find_first ~f s], where [f] is a monotonically increasing function,
returns the lowest element [e] of [s] such that [f e],
or raises [Not_found] if no such element exists.
@ -1108,21 +1108,21 @@ module type S =
*)
val find_first_opt: f:(elt -> bool) -> t -> elt option
(** [find_first_opt f s], where [f] is a monotonically increasing function,
(** [find_first_opt ~f s], where [f] is a monotonically increasing function,
returns an option containing the lowest element [e] of [s] such that
[f e], or [None] if no such element exists.
@since 4.05
*)
val find_last: f:(elt -> bool) -> t -> elt
(** [find_last f s], where [f] is a monotonically decreasing function,
(** [find_last ~f s], where [f] is a monotonically decreasing function,
returns the highest element [e] of [s] such that [f e],
or raises [Not_found] if no such element exists.
@since 4.05
*)
val find_last_opt: f:(elt -> bool) -> t -> elt option
(** [find_last_opt f s], where [f] is a monotonically decreasing function,
(** [find_last_opt ~f s], where [f] is a monotonically decreasing function,
returns an option containing the highest element [e] of [s] such that
[f e], or [None] if no such element exists.
@since 4.05

View File

@ -95,7 +95,7 @@ val make : int -> char -> string
@raise Invalid_argument if [n < 0] or [n > ]{!Sys.max_string_length}. *)
val init : int -> f:(int -> char) -> string
(** [init n f] returns a string of length [n], with character
(** [init n ~f] returns a string of length [n], with character
[i] initialized to the result of [f i] (called in increasing
index order).
@ -110,7 +110,7 @@ val copy : string -> string [@@ocaml.deprecated]
sense to make identical copies of them. *)
val sub : string -> pos:int -> len:int -> string
(** [sub s pos len] returns a fresh string of length [len],
(** [sub s ~pos ~len] returns a fresh string of length [len],
containing the substring of [s] that starts at position [pos] and
has length [len].
@raise Invalid_argument if [pos] and [len] do not
@ -118,7 +118,7 @@ val sub : string -> pos:int -> len:int -> string
val fill : bytes -> pos:int -> len:int -> char -> unit
[@@ocaml.deprecated "Use Bytes.fill/BytesLabels.fill instead."]
(** [fill s pos len c] modifies byte sequence [s] in place,
(** [fill s ~pos ~len c] modifies byte sequence [s] in place,
replacing [len] bytes by [c], starting at [pos].
@raise Invalid_argument if [pos] and [len] do not
designate a valid substring of [s].
@ -128,7 +128,7 @@ val fill : bytes -> pos:int -> len:int -> char -> unit
val blit :
src:string -> src_pos:int -> dst:bytes -> dst_pos:int -> len:int
-> unit
(** [blit src src_pos dst dst_pos len] copies [len] bytes
(** [blit ~src ~src_pos ~dst ~dst_pos ~len] copies [len] bytes
from the string [src], starting at index [src_pos],
to byte sequence [dst], starting at character number [dst_pos].
@raise Invalid_argument if [src_pos] and [len] do not
@ -136,13 +136,13 @@ val blit :
do not designate a valid range of [dst]. *)
val concat : sep:string -> string list -> string
(** [concat sep sl] concatenates the list of strings [sl],
(** [concat ~sep sl] concatenates the list of strings [sl],
inserting the separator string [sep] between each.
@raise Invalid_argument if the result is longer than
{!Sys.max_string_length} bytes. *)
val iter : f:(char -> unit) -> string -> unit
(** [iter f s] applies function [f] in turn to all
(** [iter ~f s] applies function [f] in turn to all
the characters of [s]. It is equivalent to
[f s.[0]; f s.[1]; ...; f s.[length s - 1]; ()]. *)
@ -153,13 +153,13 @@ val iteri : f:(int -> char -> unit) -> string -> unit
@since 4.00.0 *)
val map : f:(char -> char) -> string -> string
(** [map f s] applies function [f] in turn to all
(** [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.
@since 4.00.0 *)
val mapi : f:(int -> char -> char) -> string -> string
(** [mapi f s] calls [f] with each character of [s] and its
(** [mapi ~f s] calls [f] with each character of [s] and its
index (in increasing index order) and stores the results in a new
string that is returned.
@since 4.02.0 *)
@ -313,16 +313,16 @@ val uncapitalize_ascii : string -> string
val starts_with :
prefix (* comment thwarts tools/unlabel *) :string -> string -> bool
(** [starts_with prefix s] tests if [s] starts with [prefix]
(** [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
(** [ends_with suffix s] tests if [s] ends with [suffix]
(** [ends_with ~suffix s] tests if [s] ends with [suffix]
@since 4.12.0 *)
val split_on_char: sep:char -> string -> string list
(** [split_on_char sep s] returns the list of all (possibly empty)
(** [split_on_char ~sep s] returns the list of all (possibly empty)
substrings of [s] that are delimited by the [sep] character.
The function's output is specified by the following invariants:

View File

@ -79,7 +79,7 @@ val copy : ('a, 'b) t -> ('a, 'b) t
(** Return a copy of the given hashtable. *)
val add : ('a, 'b) t -> key:'a -> data:'b -> unit
(** [Hashtbl.add tbl key data] adds a binding of [key] to [data]
(** [Hashtbl.add tbl ~key ~data] adds a binding of [key] to [data]
in table [tbl].
Previous bindings for [key] are not removed, but simply
hidden. That is, after performing {!remove}[ tbl key],
@ -110,14 +110,14 @@ val remove : ('a, 'b) t -> 'a -> unit
It does nothing if [x] is not bound in [tbl]. *)
val replace : ('a, 'b) t -> key:'a -> data:'b -> unit
(** [Hashtbl.replace tbl key data] replaces the current binding of [key]
(** [Hashtbl.replace tbl ~key ~data] replaces the current binding of [key]
in [tbl] by a binding of [key] to [data]. If [key] is unbound in [tbl],
a binding of [key] to [data] is added to [tbl].
This is functionally equivalent to {!remove}[ tbl key]
followed by {!add}[ tbl key data]. *)
val iter : f:(key:'a -> data:'b -> unit) -> ('a, 'b) t -> unit
(** [Hashtbl.iter f tbl] applies [f] to all bindings in table [tbl].
(** [Hashtbl.iter ~f tbl] applies [f] to all bindings in table [tbl].
[f] receives the key as first argument, and the associated value
as second argument. Each binding is presented exactly once to [f].
@ -137,7 +137,7 @@ val iter : f:(key:'a -> data:'b -> unit) -> ('a, 'b) t -> unit
*)
val filter_map_inplace: f:(key:'a -> data:'b -> 'b option) -> ('a, 'b) t -> unit
(** [Hashtbl.filter_map_inplace f tbl] applies [f] to all bindings in
(** [Hashtbl.filter_map_inplace ~f tbl] applies [f] to all bindings in
table [tbl] and update each binding depending on the result of
[f]. If [f] returns [None], the binding is discarded. If it
returns [Some new_val], the binding is update to associate the key
@ -147,7 +147,7 @@ val filter_map_inplace: f:(key:'a -> data:'b -> 'b option) -> ('a, 'b) t -> unit
@since 4.03.0 *)
val fold : f:(key:'a -> data:'b -> 'c -> 'c) -> ('a, 'b) t -> init:'c -> 'c
(** [Hashtbl.fold f tbl init] computes
(** [Hashtbl.fold ~f tbl ~init] computes
[(f kN dN ... (f k1 d1 init)...)],
where [k1 ... kN] are the keys of all bindings in [tbl],
and [d1 ... dN] are the associated values.

View File

@ -81,7 +81,7 @@ module type S =
and [false] otherwise. *)
val add: key:key -> data:'a -> 'a t -> 'a t
(** [add key data m] returns a map containing the same bindings as
(** [add ~key ~data m] returns a map containing the same bindings as
[m], plus a binding of [key] to [data]. If [key] was already bound
in [m] to a value that is physically equal to [data],
[m] is returned unchanged (the result of the function is
@ -90,7 +90,7 @@ module type S =
@before 4.03 Physical equality was not ensured. *)
val update: key:key -> f:('a option -> 'a option) -> 'a t -> 'a t
(** [update key f m] returns a map containing the same bindings as
(** [update ~key ~f m] returns a map containing the same bindings as
[m], except for the binding of [key]. Depending on the value of
[y] where [y] is [f (find_opt key m)], the binding of [key] is
added, removed or updated. If [y] is [None], the binding is
@ -117,7 +117,7 @@ module type S =
val merge:
f:(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
(** [merge f m1 m2] computes a map whose keys are a subset of the keys of
(** [merge ~f m1 m2] computes a map whose keys are a subset of the keys of
[m1] and of [m2]. The presence of each such binding, and the
corresponding value, is determined with the function [f].
In terms of the [find_opt] operation, we have
@ -127,7 +127,7 @@ module type S =
*)
val union: f:(key -> 'a -> 'a -> 'a option) -> 'a t -> 'a t -> 'a t
(** [union f m1 m2] computes a map whose keys are a subset of the keys
(** [union ~f m1 m2] computes a map whose keys are a subset of the keys
of [m1] and of [m2]. When the same binding is defined in both
arguments, the function [f] is used to combine them.
This is a special case of [merge]: [union f m1 m2] is equivalent
@ -145,36 +145,36 @@ module type S =
used to compare data associated with equal keys in the two maps. *)
val equal: cmp:('a -> 'a -> bool) -> 'a t -> 'a t -> bool
(** [equal cmp m1 m2] tests whether the maps [m1] and [m2] are
(** [equal ~cmp m1 m2] tests whether the maps [m1] and [m2] are
equal, that is, contain equal keys and associate them with
equal data. [cmp] is the equality predicate used to compare
the data associated with the keys. *)
val iter: f:(key:key -> data:'a -> unit) -> 'a t -> unit
(** [iter f m] applies [f] to all bindings in map [m].
(** [iter ~f m] applies [f] to all bindings in map [m].
[f] receives the key as first argument, and the associated value
as second argument. The bindings are passed to [f] in increasing
order with respect to the ordering over the type of the keys. *)
val fold: f:(key:key -> data:'a -> 'b -> 'b) -> 'a t -> init:'b -> 'b
(** [fold f m init] computes [(f kN dN ... (f k1 d1 init)...)],
(** [fold ~f m ~init] computes [(f kN dN ... (f k1 d1 init)...)],
where [k1 ... kN] are the keys of all bindings in [m]
(in increasing order), and [d1 ... dN] are the associated data. *)
val for_all: f:(key -> 'a -> bool) -> 'a t -> bool
(** [for_all f m] checks if all the bindings of the map
(** [for_all ~f m] checks if all the bindings of the map
satisfy the predicate [f].
@since 3.12.0
*)
val exists: f:(key -> 'a -> bool) -> 'a t -> bool
(** [exists f m] checks if at least one binding of the map
(** [exists ~f m] checks if at least one binding of the map
satisfies the predicate [f].
@since 3.12.0
*)
val filter: f:(key -> 'a -> bool) -> 'a t -> 'a t
(** [filter f m] returns the map with all the bindings in [m]
(** [filter ~f m] returns the map with all the bindings in [m]
that satisfy predicate [p]. If every binding in [m] satisfies [f],
[m] is returned unchanged (the result of the function is then
physically equal to [m])
@ -183,7 +183,7 @@ module type S =
*)
val filter_map: f:(key -> 'a -> 'b option) -> 'a t -> 'b t
(** [filter_map f m] applies the function [f] to every binding of
(** [filter_map ~f m] applies the function [f] to every binding of
[m], and builds a map from the results. For each binding
[(k, v)] in the input map:
- if [f k v] is [None] then [k] is not in the result,
@ -203,7 +203,7 @@ module type S =
*)
val partition: f:(key -> 'a -> bool) -> 'a t -> 'a t * 'a t
(** [partition f m] returns a pair of maps [(m1, m2)], where
(** [partition ~f m] returns a pair of maps [(m1, m2)], where
[m1] contains all the bindings of [m] that satisfy the
predicate [f], and [m2] is the map with all the bindings of
[m] that do not satisfy [f].
@ -285,7 +285,7 @@ module type S =
*)
val find_first: f:(key -> bool) -> 'a t -> key * 'a
(** [find_first f m], where [f] is a monotonically increasing function,
(** [find_first ~f m], where [f] is a monotonically increasing function,
returns the binding of [m] with the lowest key [k] such that [f k],
or raises [Not_found] if no such key exists.
@ -298,28 +298,28 @@ module type S =
*)
val find_first_opt: f:(key -> bool) -> 'a t -> (key * 'a) option
(** [find_first_opt f m], where [f] is a monotonically increasing function,
(** [find_first_opt ~f m], where [f] is a monotonically increasing function,
returns an option containing the binding of [m] with the lowest key [k]
such that [f k], or [None] if no such key exists.
@since 4.05
*)
val find_last: f:(key -> bool) -> 'a t -> key * 'a
(** [find_last f m], where [f] is a monotonically decreasing function,
(** [find_last ~f m], where [f] is a monotonically decreasing function,
returns the binding of [m] with the highest key [k] such that [f k],
or raises [Not_found] if no such key exists.
@since 4.05
*)
val find_last_opt: f:(key -> bool) -> 'a t -> (key * 'a) option
(** [find_last_opt f m], where [f] is a monotonically decreasing function,
(** [find_last_opt ~f m], where [f] is a monotonically decreasing function,
returns an option containing the binding of [m] with the highest key [k]
such that [f k], or [None] if no such key exists.
@since 4.05
*)
val map: f:('a -> 'b) -> 'a t -> 'b t
(** [map f m] returns a map with same domain as [m], where the
(** [map ~f m] returns a map with same domain as [m], where the
associated value [a] of all bindings of [m] has been
replaced by the result of the application of [f] to [a].
The bindings are passed to [f] in increasing order

View File

@ -122,12 +122,12 @@ module type S =
the set [s2]. *)
val iter: f:(elt -> unit) -> t -> unit
(** [iter f s] applies [f] in turn to all elements of [s].
(** [iter ~f s] applies [f] in turn to all elements of [s].
The elements of [s] are presented to [f] in increasing order
with respect to the ordering over the type of the elements. *)
val map: f:(elt -> elt) -> t -> t
(** [map f s] is the set whose elements are [f a0],[f a1]... [f
(** [map ~f s] is the set whose elements are [f a0],[f a1]... [f
aN], where [a0],[a1]...[aN] are the elements of [s].
The elements are passed to [f] in increasing order
@ -139,26 +139,26 @@ module type S =
@since 4.04.0 *)
val fold: f:(elt -> 'a -> 'a) -> t -> init:'a -> 'a
(** [fold f s init] computes [(f xN ... (f x2 (f x1 init))...)],
(** [fold ~f s init] computes [(f xN ... (f x2 (f x1 init))...)],
where [x1 ... xN] are the elements of [s], in increasing order. *)
val for_all: f:(elt -> bool) -> t -> bool
(** [for_all f s] checks if all elements of the set
(** [for_all ~f s] checks if all elements of the set
satisfy the predicate [f]. *)
val exists: f:(elt -> bool) -> t -> bool
(** [exists f s] checks if at least one element of
(** [exists ~f s] checks if at least one element of
the set satisfies the predicate [f]. *)
val filter: f:(elt -> bool) -> t -> t
(** [filter f s] returns the set of all elements in [s]
(** [filter ~f s] returns the set of all elements in [s]
that satisfy predicate [f]. If [f] satisfies every element in [s],
[s] is returned unchanged (the result of the function is then
physically equal to [s]).
@before 4.03 Physical equality was not ensured.*)
val filter_map: f:(elt -> elt option) -> t -> t
(** [filter_map f s] returns the set of all [v] such that
(** [filter_map ~f s] returns the set of all [v] such that
[f x = Some v] for some element [x] of [s].
For example,
@ -174,7 +174,7 @@ module type S =
*)
val partition: f:(elt -> bool) -> t -> t * t
(** [partition f s] returns a pair of sets [(s1, s2)], where
(** [partition ~f s] returns a pair of sets [(s1, s2)], where
[s1] is the set of all the elements of [s] that satisfy the
predicate [f], and [s2] is the set of all the elements of
[s] that do not satisfy [f]. *)
@ -244,7 +244,7 @@ module type S =
@since 4.05 *)
val find_first: f:(elt -> bool) -> t -> elt
(** [find_first f s], where [f] is a monotonically increasing function,
(** [find_first ~f s], where [f] is a monotonically increasing function,
returns the lowest element [e] of [s] such that [f e],
or raises [Not_found] if no such element exists.
@ -257,21 +257,21 @@ module type S =
*)
val find_first_opt: f:(elt -> bool) -> t -> elt option
(** [find_first_opt f s], where [f] is a monotonically increasing function,
(** [find_first_opt ~f s], where [f] is a monotonically increasing function,
returns an option containing the lowest element [e] of [s] such that
[f e], or [None] if no such element exists.
@since 4.05
*)
val find_last: f:(elt -> bool) -> t -> elt
(** [find_last f s], where [f] is a monotonically decreasing function,
(** [find_last ~f s], where [f] is a monotonically decreasing function,
returns the highest element [e] of [s] such that [f e],
or raises [Not_found] if no such element exists.
@since 4.05
*)
val find_last_opt: f:(elt -> bool) -> t -> elt option
(** [find_last_opt f s], where [f] is a monotonically decreasing function,
(** [find_last_opt ~f s], where [f] is a monotonically decreasing function,
returns an option containing the highest element [e] of [s] such that
[f e], or [None] if no such element exists.
@since 4.05

View File

@ -30,9 +30,9 @@ LABREGEX="s/ [a-z_]+:([a-z\('])/ \1/g"
#A second, sligthly different round sometimes required to deal with f:(key:key
LABLABREGEX="s/\([a-z_]+:([a-z\('])/\(\1/g"
#Remove a tilde if it is followed by some alphanumerics and a space or closing
#Remove a tilde if it is followed by a label name and a space or closing
#OCamldoc code section with ]
TILDEREGEX="s/~([a-z]*[ \]])/\1/g"
TILDEREGEX="s/~([a-z_]*[ \]])/\1/g"
#Stdlib
perl -p -e "$LABREGEX" stdlib/listLabels.mli > stdlib/list.temp.mli
@ -74,7 +74,7 @@ perl -p -e 's/MAP/`tail -n +19 stdlib\/templates\/map.template.mli`/e' \
perl -p -e 's/SET/`tail -n +19 stdlib\/templates\/set.template.mli`/e' \
stdlib/moreLabels.2temp.mli > stdlib/moreLabels.mli
#Fix up
#Fix up with templates in tools/unlabel-patches
perl -p -e "s/type statistics =/type statistics = Hashtbl\.statistics =/" \
stdlib/moreLabels.mli > stdlib/moreLabels.temp.mli
perl -p -e "s/type \(!'a, !'b\) t/type \(!'a, !'b\) t = \('a, 'b) Hashtbl.t/" \