summaryrefslogtreecommitdiff
path: root/stdlib/ephemeron.mli
diff options
context:
space:
mode:
authorKC Sivaramakrishnan <kc@kcsrk.info>2021-11-11 15:22:46 +0530
committerKC Sivaramakrishnan <kc@kcsrk.info>2021-11-11 15:22:46 +0530
commit18ae86e427de027cde80f35f32c011af0b2ed80c (patch)
tree14482ade7fed88b3f3285ad0b04a9bcb393d1e0f /stdlib/ephemeron.mli
parentd9bdc3cb4564ca58928e906da5fa361efcf6d920 (diff)
downloadocaml-18ae86e427de027cde80f35f32c011af0b2ed80c.tar.gz
Make ephemerons immutable.
This is a port of https://github.com/ocaml/ocaml/pull/10737 for multicore.
Diffstat (limited to 'stdlib/ephemeron.mli')
-rw-r--r--stdlib/ephemeron.mli327
1 files changed, 121 insertions, 206 deletions
diff --git a/stdlib/ephemeron.mli b/stdlib/ephemeron.mli
index f15151244d..e12d48052a 100644
--- a/stdlib/ephemeron.mli
+++ b/stdlib/ephemeron.mli
@@ -75,7 +75,24 @@ module type S = sig
Use [filter_map_inplace] in this case.
*)
- include Hashtbl.S
+ type key
+ type !'a t
+ val create : int -> 'a t
+ val clear : 'a t -> unit
+ val reset : 'a t -> unit
+ val copy : 'a t -> 'a t
+ val add : 'a t -> key -> 'a -> unit
+ val remove : 'a t -> key -> unit
+ val find : 'a t -> key -> 'a
+ val find_opt : 'a t -> key -> 'a option
+ val find_all : 'a t -> key -> 'a list
+ val replace : 'a t -> key -> 'a -> unit
+ val mem : 'a t -> key -> bool
+ val length : 'a t -> int
+ val stats : 'a t -> Hashtbl.statistics
+ val add_seq : 'a t -> (key * 'a) Seq.t -> unit
+ val replace_seq : 'a t -> (key * 'a) Seq.t -> unit
+ val of_seq : (key * 'a) Seq.t -> 'a t
val clean: 'a t -> unit
(** remove all dead bindings. Done automatically during automatic resizing. *)
@@ -83,102 +100,52 @@ module type S = sig
val stats_alive: 'a t -> Hashtbl.statistics
(** same as {!Hashtbl.SeededS.stats} but only count the alive bindings *)
end
-(** The output signature of the functor {!K1.Make} and {!K2.Make}.
+(** The output signature of the functors {!K1.Make} and {!K2.Make}.
These hash tables are weak in the keys. If all the keys of a binding are
alive the binding is kept, but if one of the keys of the binding
is dead then the binding is removed.
*)
module type SeededS = sig
- include Hashtbl.SeededS
+
+ type key
+ type !'a t
+ val create : ?random (*thwart tools/sync_stdlib_docs*) : bool -> int -> 'a t
+ val clear : 'a t -> unit
+ val reset : 'a t -> unit
+ val copy : 'a t -> 'a t
+ val add : 'a t -> key -> 'a -> unit
+ val remove : 'a t -> key -> unit
+ val find : 'a t -> key -> 'a
+ val find_opt : 'a t -> key -> 'a option
+ val find_all : 'a t -> key -> 'a list
+ val replace : 'a t -> key -> 'a -> unit
+ val mem : 'a t -> key -> bool
+ val length : 'a t -> int
+ val stats : 'a t -> Hashtbl.statistics
+ val add_seq : 'a t -> (key * 'a) Seq.t -> unit
+ val replace_seq : 'a t -> (key * 'a) Seq.t -> unit
+ val of_seq : (key * 'a) Seq.t -> 'a t
+
val clean: 'a t -> unit
(** remove all dead bindings. Done automatically during automatic resizing. *)
val stats_alive: 'a t -> Hashtbl.statistics
(** same as {!Hashtbl.SeededS.stats} but only count the alive bindings *)
end
-(** The output signature of the functor {!K1.MakeSeeded} and {!K2.MakeSeeded}.
+(** The output signature of the functors {!K1.MakeSeeded} and {!K2.MakeSeeded}.
*)
module K1 : sig
type ('k,'d) t (** an ephemeron with one key *)
- val create: unit -> ('k,'d) t
- (** [Ephemeron.K1.create ()] creates an ephemeron with one key. The
- data and the key are empty *)
-
- val get_key: ('k,'d) t -> 'k option
- (** [Ephemeron.K1.get_key eph] returns [None] if the key of [eph] is
- empty, [Some x] (where [x] is the key) if it is full. *)
-
- val get_key_copy: ('k,'d) t -> 'k option
- (** [Ephemeron.K1.get_key_copy eph] returns [None] if the key of [eph] is
- empty, [Some x] (where [x] is a (shallow) copy of the key) if
- it is full. This function has the same GC friendliness as {!Weak.get_copy}
-
- If the element is a custom block it is not copied.
- *)
-
- val set_key: ('k,'d) t -> 'k -> unit
- (** [Ephemeron.K1.set_key eph el] sets the key of [eph] to be a
- (full) key to [el]
- *)
-
- val unset_key: ('k,'d) t -> unit
- (** [Ephemeron.K1.unset_key eph el] sets the key of [eph] to be an
- empty key. Since there is only one key, the ephemeron starts
- behaving like a reference on the data. *)
-
- val check_key: ('k,'d) t -> bool
- (** [Ephemeron.K1.check_key eph] returns [true] if the key of the [eph]
- is full, [false] if it is empty. Note that even if
- [Ephemeron.K1.check_key eph] returns [true], a subsequent
- {!Ephemeron.K1.get_key}[eph] can return [None].
- *)
-
-
- val blit_key : ('k,_) t -> ('k,_) t -> unit
- (** [Ephemeron.K1.blit_key eph1 eph2] sets the key of [eph2] with
- the key of [eph1]. Contrary to using {!Ephemeron.K1.get_key}
- followed by {!Ephemeron.K1.set_key} or {!Ephemeron.K1.unset_key}
- this function does not prevent the incremental GC from erasing
- the value in its current cycle. *)
-
- val get_data: ('k,'d) t -> 'd option
- (** [Ephemeron.K1.get_data eph] returns [None] if the data of [eph] is
- empty, [Some x] (where [x] is the data) if it is full. *)
+ val make : 'k -> 'd -> ('k,'d) t
+ (** [Ephemeron.K1.make k d] creates an ephemeron with key [k] and data [d]. *)
- val get_data_copy: ('k,'d) t -> 'd option
- (** [Ephemeron.K1.get_data_copy eph] returns [None] if the data of [eph] is
- empty, [Some x] (where [x] is a (shallow) copy of the data) if
- it is full. This function has the same GC friendliness as {!Weak.get_copy}
-
- If the element is a custom block it is not copied.
- *)
-
- val set_data: ('k,'d) t -> 'd -> unit
- (** [Ephemeron.K1.set_data eph el] sets the data of [eph] to be a
- (full) data to [el]
- *)
-
- val unset_data: ('k,'d) t -> unit
- (** [Ephemeron.K1.unset_data eph el] sets the key of [eph] to be an
- empty key. The ephemeron starts behaving like a weak pointer.
- *)
-
- val check_data: ('k,'d) t -> bool
- (** [Ephemeron.K1.check_data eph] returns [true] if the data of the [eph]
- is full, [false] if it is empty. Note that even if
- [Ephemeron.K1.check_data eph] returns [true], a subsequent
- {!Ephemeron.K1.get_data}[eph] can return [None].
- *)
-
- val blit_data : (_,'d) t -> (_,'d) t -> unit
- (** [Ephemeron.K1.blit_data eph1 eph2] sets the data of [eph2] with
- the data of [eph1]. Contrary to using {!Ephemeron.K1.get_data}
- followed by {!Ephemeron.K1.set_data} or {!Ephemeron.K1.unset_data}
- this function does not prevent the incremental GC from erasing
- the value in its current cycle. *)
+ val query : ('k,'d) t -> 'k -> 'd option
+ (** [Ephemeron.K1.query eph key] returns [Some x] (where [x] is the
+ ephemeron's data) if [key] is physically equal to [eph]'s key, and
+ [None] if [eph] is empty or [key] is not equal to [eph]'s key. *)
module Make (H:Hashtbl.HashedType) : S with type key = H.t
(** Functor building an implementation of a weak hash table *)
@@ -187,71 +154,45 @@ module K1 : sig
(** Functor building an implementation of a weak hash table.
The seed is similar to the one of {!Hashtbl.MakeSeeded}. *)
-end
-(** Ephemerons with one key. *)
-
-module K2 : sig
- type ('k1,'k2,'d) t (** an ephemeron with two keys *)
-
- val create: unit -> ('k1,'k2,'d) t
- (** Same as {!Ephemeron.K1.create} *)
-
- val get_key1: ('k1,'k2,'d) t -> 'k1 option
- (** Same as {!Ephemeron.K1.get_key} *)
-
- val get_key1_copy: ('k1,'k2,'d) t -> 'k1 option
- (** Same as {!Ephemeron.K1.get_key_copy} *)
-
- val set_key1: ('k1,'k2,'d) t -> 'k1 -> unit
- (** Same as {!Ephemeron.K1.set_key} *)
-
- val unset_key1: ('k1,'k2,'d) t -> unit
- (** Same as {!Ephemeron.K1.unset_key} *)
-
- val check_key1: ('k1,'k2,'d) t -> bool
- (** Same as {!Ephemeron.K1.check_key} *)
+ module Bucket : sig
- val get_key2: ('k1,'k2,'d) t -> 'k2 option
- (** Same as {!Ephemeron.K1.get_key} *)
+ type ('k, 'd) t
+ (** A bucket is a mutable "list" of ephemerons. *)
- val get_key2_copy: ('k1,'k2,'d) t -> 'k2 option
- (** Same as {!Ephemeron.K1.get_key_copy} *)
+ val make : unit -> ('k, 'd) t
+ (** Create a new bucket. *)
- val set_key2: ('k1,'k2,'d) t -> 'k2 -> unit
- (** Same as {!Ephemeron.K1.set_key} *)
+ val add : ('k, 'd) t -> 'k -> 'd -> unit
+ (** Add an ephemeron to the bucket. *)
- val unset_key2: ('k1,'k2,'d) t -> unit
- (** Same as {!Ephemeron.K1.unset_key} *)
+ val remove : ('k, 'd) t -> 'k -> unit
+ (** [remove b k] removes from [b] the most-recently added
+ ephemeron with key [k], or does nothing if there is no such
+ ephemeron. *)
- val check_key2: ('k1,'k2,'d) t -> bool
- (** Same as {!Ephemeron.K1.check_key} *)
+ val find : ('k, 'd) t -> 'k -> 'd option
+ (** Returns the data of the most-recently added ephemeron with the
+ given key, or [None] if there is no such ephemeron. *)
- val blit_key1: ('k1,_,_) t -> ('k1,_,_) t -> unit
- (** Same as {!Ephemeron.K1.blit_key} *)
+ val length : ('k, 'd) t -> int
+ (** Returns an upper bound on the length of the bucket. *)
- val blit_key2: (_,'k2,_) t -> (_,'k2,_) t -> unit
- (** Same as {!Ephemeron.K1.blit_key} *)
+ val clear : ('k, 'd) t -> unit
+ (** Remove all ephemerons from the bucket. *)
- val blit_key12: ('k1,'k2,_) t -> ('k1,'k2,_) t -> unit
- (** Same as {!Ephemeron.K1.blit_key} *)
+ end
- val get_data: ('k1,'k2,'d) t -> 'd option
- (** Same as {!Ephemeron.K1.get_data} *)
-
- val get_data_copy: ('k1,'k2,'d) t -> 'd option
- (** Same as {!Ephemeron.K1.get_data_copy} *)
-
- val set_data: ('k1,'k2,'d) t -> 'd -> unit
- (** Same as {!Ephemeron.K1.set_data} *)
+end
+(** Ephemerons with one key. *)
- val unset_data: ('k1,'k2,'d) t -> unit
- (** Same as {!Ephemeron.K1.unset_data} *)
+module K2 : sig
+ type ('k1,'k2,'d) t (** an ephemeron with two keys *)
- val check_data: ('k1,'k2,'d) t -> bool
- (** Same as {!Ephemeron.K1.check_data} *)
+ val make : 'k1 -> 'k2 -> 'd -> ('k1,'k2,'d) t
+ (** Same as {!Ephemeron.K1.make} *)
- val blit_data: ('k1,'k2,'d) t -> ('k1,'k2,'d) t -> unit
- (** Same as {!Ephemeron.K1.blit_data} *)
+ val query : ('k1,'k2,'d) t -> 'k1 -> 'k2 -> 'd option
+ (** Same as {!Ephemeron.K1.query} *)
module Make
(H1:Hashtbl.HashedType)
@@ -266,51 +207,46 @@ module K2 : sig
(** Functor building an implementation of a weak hash table.
The seed is similar to the one of {!Hashtbl.MakeSeeded}. *)
-end
-(** Emphemerons with two keys. *)
+ module Bucket : sig
-module Kn : sig
- type ('k,'d) t (** an ephemeron with an arbitrary number of keys
- of the same type *)
-
- val create: int -> ('k,'d) t
- (** Same as {!Ephemeron.K1.create} *)
+ type ('k1, 'k2, 'd) t
+ (** A bucket is a mutable "list" of ephemerons. *)
- val get_key: ('k,'d) t -> int -> 'k option
- (** Same as {!Ephemeron.K1.get_key} *)
+ val make : unit -> ('k1, 'k2, 'd) t
+ (** Create a new bucket. *)
- val get_key_copy: ('k,'d) t -> int -> 'k option
- (** Same as {!Ephemeron.K1.get_key_copy} *)
+ val add : ('k1, 'k2, 'd) t -> 'k1 -> 'k2 -> 'd -> unit
+ (** Add an ephemeron to the bucket. *)
- val set_key: ('k,'d) t -> int -> 'k -> unit
- (** Same as {!Ephemeron.K1.set_key} *)
+ val remove : ('k1, 'k2, 'd) t -> 'k1 -> 'k2 -> unit
+ (** [remove b k1 k2] removes from [b] the most-recently added
+ ephemeron with keys [k1] and [k2], or does nothing if there
+ is no such ephemeron. *)
- val unset_key: ('k,'d) t -> int -> unit
- (** Same as {!Ephemeron.K1.unset_key} *)
+ val find : ('k1, 'k2, 'd) t -> 'k1 -> 'k2 -> 'd option
+ (** Returns the data of the most-recently added ephemeron with the
+ given keys, or [None] if there is no such ephemeron. *)
- val check_key: ('k,'d) t -> int -> bool
- (** Same as {!Ephemeron.K1.check_key} *)
+ val length : ('k1, 'k2, 'd) t -> int
+ (** Returns an upper bound on the length of the bucket. *)
- val blit_key: ('k,_) t -> int -> ('k,_) t -> int -> int -> unit
- (** Same as {!Ephemeron.K1.blit_key} *)
+ val clear : ('k1, 'k2, 'd) t -> unit
+ (** Remove all ephemerons from the bucket. *)
- val get_data: ('k,'d) t -> 'd option
- (** Same as {!Ephemeron.K1.get_data} *)
+ end
- val get_data_copy: ('k,'d) t -> 'd option
- (** Same as {!Ephemeron.K1.get_data_copy} *)
-
- val set_data: ('k,'d) t -> 'd -> unit
- (** Same as {!Ephemeron.K1.set_data} *)
+end
+(** Ephemerons with two keys. *)
- val unset_data: ('k,'d) t -> unit
- (** Same as {!Ephemeron.K1.unset_data} *)
+module Kn : sig
+ type ('k,'d) t (** an ephemeron with an arbitrary number of keys
+ of the same type *)
- val check_data: ('k,'d) t -> bool
- (** Same as {!Ephemeron.K1.check_data} *)
+ val make : 'k array -> 'd -> ('k,'d) t
+ (** Same as {!Ephemeron.K1.make} *)
- val blit_data: ('k,'d) t -> ('k,'d) t -> unit
- (** Same as {!Ephemeron.K1.blit_data} *)
+ val query : ('k,'d) t -> 'k array -> 'd option
+ (** Same as {!Ephemeron.K1.query} *)
module Make
(H:Hashtbl.HashedType) :
@@ -323,54 +259,33 @@ module Kn : sig
(** Functor building an implementation of a weak hash table.
The seed is similar to the one of {!Hashtbl.MakeSeeded}. *)
-end
-(** Emphemerons with arbitrary number of keys of the same type. *)
-
-module GenHashTable: sig
- (** Define a hash table on generic containers which have a notion of
- "death" and aliveness. If a binding is dead the hash table can
- automatically remove it. *)
-
- type equal =
- | ETrue
- | EFalse
- | EDead (** the container is dead *)
-
- module MakeSeeded(H:
- sig
- type t
- (** keys *)
+ module Bucket : sig
- type 'a container
- (** contains keys and the associated data *)
+ type ('k, 'd) t
+ (** A bucket is a mutable "list" of ephemerons. *)
- val hash: int -> t -> int
- (** same as {!Hashtbl.SeededHashedType} *)
+ val make : unit -> ('k, 'd) t
+ (** Create a new bucket. *)
- val equal: 'a container -> t -> equal
- (** equality predicate used to compare a key with the one in a
- container. Can return [EDead] if the keys in the container are
- dead *)
+ val add : ('k, 'd) t -> 'k array -> 'd -> unit
+ (** Add an ephemeron to the bucket. *)
- val create: t -> 'a -> 'a container
- (** [create key data] creates a container from
- some initials keys and one data *)
+ val remove : ('k, 'd) t -> 'k array -> unit
+ (** [remove b k] removes from [b] the most-recently added
+ ephemeron with keys [k], or does nothing if there is no such
+ ephemeron. *)
- val get_key: 'a container -> t option
- (** [get_key cont] returns the keys if they are all alive *)
+ val find : ('k, 'd) t -> 'k array -> 'd option
+ (** Returns the data of the most-recently added ephemeron with the
+ given keys, or [None] if there is no such ephemeron. *)
- val get_data: 'a container -> 'a option
- (** [get_data cont] returns the data if it is alive *)
+ val length : ('k, 'd) t -> int
+ (** Returns an upper bound on the length of the bucket. *)
- val set_key_data: 'a container -> t -> 'a -> unit
- (** [set_key_data cont] modifies the key and data *)
+ val clear : ('k, 'd) t -> unit
+ (** Remove all ephemerons from the bucket. *)
- val check_key: 'a container -> bool
- (** [check_key cont] checks if all the keys contained in the data
- are alive *)
- end) : SeededS with type key = H.t
- (** Functor building an implementation of an hash table that use the container
- for keeping the information given *)
+ end
end
-(** Hash tables on generic containers with notion of death and aliveness. *)
+(** Ephemerons with arbitrary number of keys of the same type. *)