Module Hashtbl.MakeSeededSource

Functor building an implementation of the hashtable structure. The functor Hashtbl.MakeSeeded returns a structure containing a type key of keys and a type 'a t of hash tables associating data of type 'a to keys of type key. The operations perform similarly to those of the generic interface, but use the seeded hashing and equality functions specified in the functor argument H instead of generic equality and hashing. The create operation of the result structure supports the ~random optional parameter and returns randomized hash tables if ~random:true is passed or if randomization is globally on (see Hashtbl.randomize).

Parameters

Signature

Sourcetype key = H.t
Sourcetype !'a t
Sourceval create : ?random:bool -> int -> 'a t
Sourceval clear : 'a t -> unit
Sourceval reset : 'a t -> unit
Sourceval copy : 'a t -> 'a t
Sourceval add : 'a t -> key -> 'a -> unit
Sourceval remove : 'a t -> key -> unit
Sourceval find : 'a t -> key -> 'a
Sourceval find_opt : 'a t -> key -> 'a option
  • since 4.05
Sourceval find_all : 'a t -> key -> 'a list
Sourceval replace : 'a t -> key -> 'a -> unit
Sourceval mem : 'a t -> key -> bool
Sourceval iter : (key -> 'a -> unit) -> 'a t -> unit
Sourceval filter_map_inplace : (key -> 'a -> 'a option) -> 'a t -> unit
  • since 4.03
Sourceval fold : (key -> 'a -> 'acc -> 'acc) -> 'a t -> 'acc -> 'acc
Sourceval length : 'a t -> int
Sourceval stats : 'a t -> statistics
Sourceval to_seq : 'a t -> (key * 'a) Seq.t
  • since 4.07
Sourceval to_seq_keys : _ t -> key Seq.t
  • since 4.07
Sourceval to_seq_values : 'a t -> 'a Seq.t
  • since 4.07
Sourceval add_seq : 'a t -> (key * 'a) Seq.t -> unit
  • since 4.07
Sourceval replace_seq : 'a t -> (key * 'a) Seq.t -> unit
  • since 4.07
Sourceval of_seq : (key * 'a) Seq.t -> 'a t
  • since 4.07