Check-typo and indenting all done

master
John Whitington 2020-07-31 14:24:50 +01:00
parent 4c5879b079
commit a5ed794b4c
9 changed files with 1148 additions and 1109 deletions

View File

@ -50,13 +50,13 @@ val create : ?random: (* thwart tools/unlabel *) bool -> int -> ('a, 'b) t
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
different collision patterns, rendering ineffective the denial-of-service
attack described above. However, because of randomization, enumerating all
elements of the hash table using {!fold} or {!iter} is no longer
deterministic: elements are enumerated in different orders at different runs
of the program.
table creation time. In effect, the hash function used is randomly
selected among [2^{30}] different hash functions. All these hash
functions have different collision patterns, rendering ineffective the
denial-of-service attack described above. However, because of
randomization, enumerating all elements of the hash table using {!fold}
or {!iter} is no longer deterministic: elements are enumerated in
different orders at different runs of the program.
If no [random] parameter is given, hash tables are created
in non-random mode by default. This default can be changed
@ -136,7 +136,8 @@ val iter : ('a -> 'b -> unit) -> ('a, 'b) t -> unit
by [f] during the iteration.
*)
val filter_map_inplace: ('a -> 'b -> 'b option) -> ('a, 'b) t -> unit
val filter_map_inplace: ('a -> 'b -> 'b option) -> ('a, 'b) t ->
unit
(** [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
@ -346,7 +347,8 @@ module type S =
val replace : 'a t -> key -> 'a -> unit
val mem : 'a t -> key -> bool
val iter : (key -> 'a -> unit) -> 'a t -> unit
val filter_map_inplace: (key -> 'a -> 'a option) -> 'a t -> unit
val filter_map_inplace: (key -> 'a -> 'a option) -> 'a t ->
unit
(** @since 4.03.0 *)
val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
@ -420,7 +422,8 @@ module type SeededS =
val replace : 'a t -> key -> 'a -> unit
val mem : 'a t -> key -> bool
val iter : (key -> 'a -> unit) -> 'a t -> unit
val filter_map_inplace: (key -> 'a -> 'a option) -> 'a t -> unit
val filter_map_inplace: (key -> 'a -> 'a option) -> 'a t ->
unit
(** @since 4.03.0 *)
val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b

View File

@ -103,8 +103,8 @@ module type S =
*)
val singleton: key -> 'a -> 'a t
(** [singleton x y] returns the one-element map that contains a binding [y]
for [x].
(** [singleton x y] returns the one-element map that contains a binding
[y] for [x].
@since 3.12.0
*)
@ -116,7 +116,8 @@ module type S =
@before 4.03 Physical equality was not ensured. *)
val merge:
(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
(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
[m1] and of [m2]. The presence of each such binding, and the
corresponding value, is determined with the function [f].
@ -291,16 +292,16 @@ module type S =
For example, [find_first (fun k -> Ord.compare k x >= 0) m] will return
the first binding [k, v] of [m] where [Ord.compare k x >= 0]
(intuitively: [k >= x]), or raise [Not_found] if [x] is greater than any
element of [m].
(intuitively: [k >= x]), or raise [Not_found] if [x] is greater than
any element of [m].
@since 4.05
*)
val find_first_opt: (key -> bool) -> 'a t -> (key * 'a) option
(** [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.
(** [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
*)
@ -312,9 +313,10 @@ module type S =
*)
val find_last_opt: (key -> bool) -> 'a t -> (key * 'a) option
(** [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.
(** [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
*)

File diff suppressed because it is too large Load Diff

View File

@ -257,9 +257,9 @@ module type S =
*)
val find_first_opt: (elt -> bool) -> t -> elt option
(** [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.
(** [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
*)
@ -271,9 +271,9 @@ module type S =
*)
val find_last_opt: (elt -> bool) -> t -> elt option
(** [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.
(** [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

@ -50,13 +50,13 @@ val create : ?random: (* thwart tools/unlabel *) bool -> int -> ('a, 'b) t
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
different collision patterns, rendering ineffective the denial-of-service
attack described above. However, because of randomization, enumerating all
elements of the hash table using {!fold} or {!iter} is no longer
deterministic: elements are enumerated in different orders at different runs
of the program.
table creation time. In effect, the hash function used is randomly
selected among [2^{30}] different hash functions. All these hash
functions have different collision patterns, rendering ineffective the
denial-of-service attack described above. However, because of
randomization, enumerating all elements of the hash table using {!fold}
or {!iter} is no longer deterministic: elements are enumerated in
different orders at different runs of the program.
If no [~random] parameter is given, hash tables are created
in non-random mode by default. This default can be changed
@ -136,7 +136,8 @@ val iter : f:(key:'a -> data:'b -> unit) -> ('a, 'b) t -> unit
by [f] during the iteration.
*)
val filter_map_inplace: f:(key:'a -> data:'b -> 'b option) -> ('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
table [tbl] and update each binding depending on the result of
[f]. If [f] returns [None], the binding is discarded. If it
@ -346,7 +347,8 @@ module type S =
val replace : 'a t -> key:key -> data:'a -> unit
val mem : 'a t -> key -> bool
val iter : f:(key:key -> data:'a -> unit) -> 'a t -> unit
val filter_map_inplace: f:(key:key -> data:'a -> 'a option) -> 'a t -> unit
val filter_map_inplace: f:(key:key -> data:'a -> 'a option) -> 'a t ->
unit
(** @since 4.03.0 *)
val fold : f:(key:key -> data:'a -> 'b -> 'b) -> 'a t -> init:'b -> 'b
@ -420,7 +422,8 @@ module type SeededS =
val replace : 'a t -> key:key -> data:'a -> unit
val mem : 'a t -> key -> bool
val iter : f:(key:key -> data:'a -> unit) -> 'a t -> unit
val filter_map_inplace: f:(key:key -> data:'a -> 'a option) -> 'a t -> unit
val filter_map_inplace: f:(key:key -> data:'a -> 'a option) -> 'a t ->
unit
(** @since 4.03.0 *)
val fold : f:(key:key -> data:'a -> 'b -> 'b) -> 'a t -> init:'b -> 'b

View File

@ -103,8 +103,8 @@ module type S =
*)
val singleton: key -> 'a -> 'a t
(** [singleton x y] returns the one-element map that contains a binding [y]
for [x].
(** [singleton x y] returns the one-element map that contains a binding
[y] for [x].
@since 3.12.0
*)
@ -116,7 +116,8 @@ module type S =
@before 4.03 Physical equality was not ensured. *)
val merge:
f:(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
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
[m1] and of [m2]. The presence of each such binding, and the
corresponding value, is determined with the function [f].
@ -291,16 +292,16 @@ module type S =
For example, [find_first (fun k -> Ord.compare k x >= 0) m] will return
the first binding [k, v] of [m] where [Ord.compare k x >= 0]
(intuitively: [k >= x]), or raise [Not_found] if [x] is greater than any
element of [m].
(intuitively: [k >= x]), or raise [Not_found] if [x] is greater than
any element of [m].
@since 4.05
*)
val find_first_opt: f:(key -> bool) -> 'a t -> (key * 'a) option
(** [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.
(** [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
*)
@ -312,9 +313,10 @@ module type S =
*)
val find_last_opt: f:(key -> bool) -> 'a t -> (key * 'a) option
(** [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.
(** [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
*)

View File

@ -18,12 +18,18 @@
(** Extra labeled libraries.
This meta-module provides labelized version of the {!Hashtbl},
{!Map} and {!Set} modules.
This meta-module provides labelized versions of the {!Hashtbl}, {!Map} and
{!Set} modules.
They only differ by their labels. They are provided to help
porting from previous versions of OCaml.
The contents of this module are subject to change.
This module is intended to be used through [open MoreLabels] which replaces
{!Hashtbl}, {!Map}, and {!Set} with their labeled counterparts.
For example:
{[
open MoreLabels
Hashtbl.iter ~f:(fun ~key ~data -> g key data) table
]}
*)
module Hashtbl : sig

View File

@ -257,9 +257,9 @@ 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,
returns an option containing the lowest element [e] of [s] such that
[f e], or [None] if no such element exists.
(** [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
*)
@ -271,9 +271,9 @@ module type S =
*)
val find_last_opt: f:(elt -> bool) -> t -> elt option
(** [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.
(** [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

@ -34,9 +34,12 @@ LABLABREGEX="s/\([a-z_]+:([a-z\('])/\(\1/g"
#OCamldoc code section with ]
TILDEREGEX="s/~([a-z_]*[ \]])/\1/g"
# @sinceunlabeled --> @since
#@sinceunlabeled --> @since
SINCEREGEX="s/sinceunlabeled/since/g"
#Indent a non-blank line by two characters, for moreLabels templates
INDENTREGEX="s/^(.+)$/ \1/m"
#Stdlib
perl -p -e "$LABREGEX" stdlib/listLabels.mli > stdlib/list.temp.mli
perl -p -e "$LABREGEX" stdlib/arrayLabels.mli > stdlib/array.temp.mli
@ -76,13 +79,21 @@ perl -p -e "$TILDEREGEX" stdlib/set.2temp.mli > stdlib/set.mli
#(No @since problems in MoreLabels)
#Indent the labeled modules
perl -p -e "$INDENTREGEX" stdlib/templates/hashtbl.template.mli > \
stdlib/templates/hashtbl.template.temp.mli
perl -p -e "$INDENTREGEX" stdlib/templates/map.template.mli > \
stdlib/templates/map.template.temp.mli
perl -p -e "$INDENTREGEX" stdlib/templates/set.template.mli > \
stdlib/templates/set.template.temp.mli
#Substitute the labeled modules in to moreLabels.mli
perl -p -e\
's/HASHTBL/`tail -n +19 stdlib\/templates\/hashtbl.template.mli`/e' \
's/HASHTBL/`tail -n +19 stdlib\/templates\/hashtbl.template.temp.mli`/e' \
stdlib/templates/moreLabels.template.mli > stdlib/moreLabels.temp.mli
perl -p -e 's/MAP/`tail -n +19 stdlib\/templates\/map.template.mli`/e' \
perl -p -e 's/MAP/`tail -n +19 stdlib\/templates\/map.template.temp.mli`/e' \
stdlib/moreLabels.temp.mli > stdlib/moreLabels.2temp.mli
perl -p -e 's/SET/`tail -n +19 stdlib\/templates\/set.template.mli`/e' \
perl -p -e 's/SET/`tail -n +19 stdlib\/templates\/set.template.temp.mli`/e' \
stdlib/moreLabels.2temp.mli > stdlib/moreLabels.mli
#Fix up with templates in tools/unlabel-patches
@ -126,3 +137,4 @@ perl -p -e 's/ = Unix.LargeFile.stats//' \
#Clean up
rm -f stdlib/*temp.mli
rm -f otherlibs/unix/*temp.mli
rm -f stdlib/templates/*temp.mli