Sys.Signals module for a Variant type of signals (and a set_signal function that...
[ocaml.git] / stdlib / weak.mli
bloba0b794e6645e178c2ab4b39a169a762ae88aa348
1 (***********************************************************************)
2 (* *)
3 (* Objective Caml *)
4 (* *)
5 (* Damien Doligez, projet Para, INRIA Rocquencourt *)
6 (* *)
7 (* Copyright 1997 Institut National de Recherche en Informatique et *)
8 (* en Automatique. All rights reserved. This file is distributed *)
9 (* under the terms of the GNU Library General Public License, with *)
10 (* the special exception on linking described in file ../LICENSE. *)
11 (* *)
12 (***********************************************************************)
14 (* $Id$ *)
16 (** Arrays of weak pointers and hash tables of weak pointers. *)
19 (** {6 Low-level functions} *)
21 type 'a t
22 (** The type of arrays of weak pointers (weak arrays). A weak
23 pointer is a value that the garbage collector may erase at
24 any time.
25 A weak pointer is said to be full if it points to a value,
26 empty if the value was erased by the GC.
27 Note that weak arrays cannot be marshaled using
28 {!Pervasives.output_value} or the functions of the {!Marshal}
29 module.
33 val create : int -> 'a t
34 (** [Weak.create n] returns a new weak array of length [n].
35 All the pointers are initially empty. Raise [Invalid_argument]
36 if [n] is negative or greater than {!Sys.max_array_length}[-1].*)
38 val length : 'a t -> int
39 (** [Weak.length ar] returns the length (number of elements) of
40 [ar].*)
42 val set : 'a t -> int -> 'a option -> unit
43 (** [Weak.set ar n (Some el)] sets the [n]th cell of [ar] to be a
44 (full) pointer to [el]; [Weak.set ar n None] sets the [n]th
45 cell of [ar] to empty.
46 Raise [Invalid_argument "Weak.set"] if [n] is not in the range
47 0 to {!Weak.length}[ a - 1].*)
49 val get : 'a t -> int -> 'a option
50 (** [Weak.get ar n] returns None if the [n]th cell of [ar] is
51 empty, [Some x] (where [x] is the value) if it is full.
52 Raise [Invalid_argument "Weak.get"] if [n] is not in the range
53 0 to {!Weak.length}[ a - 1].*)
55 val get_copy : 'a t -> int -> 'a option
56 (** [Weak.get_copy ar n] returns None if the [n]th cell of [ar] is
57 empty, [Some x] (where [x] is a (shallow) copy of the value) if
58 it is full.
59 In addition to pitfalls with mutable values, the interesting
60 difference with [get] is that [get_copy] does not prevent
61 the incremental GC from erasing the value in its current cycle
62 ([get] may delay the erasure to the next GC cycle).
63 Raise [Invalid_argument "Weak.get"] if [n] is not in the range
64 0 to {!Weak.length}[ a - 1].*)
67 val check : 'a t -> int -> bool
68 (** [Weak.check ar n] returns [true] if the [n]th cell of [ar] is
69 full, [false] if it is empty. Note that even if [Weak.check ar n]
70 returns [true], a subsequent {!Weak.get}[ ar n] can return [None].*)
72 val fill : 'a t -> int -> int -> 'a option -> unit
73 (** [Weak.fill ar ofs len el] sets to [el] all pointers of [ar] from
74 [ofs] to [ofs + len - 1]. Raise [Invalid_argument "Weak.fill"]
75 if [ofs] and [len] do not designate a valid subarray of [a].*)
77 val blit : 'a t -> int -> 'a t -> int -> int -> unit
78 (** [Weak.blit ar1 off1 ar2 off2 len] copies [len] weak pointers
79 from [ar1] (starting at [off1]) to [ar2] (starting at [off2]).
80 It works correctly even if [ar1] and [ar2] are the same.
81 Raise [Invalid_argument "Weak.blit"] if [off1] and [len] do
82 not designate a valid subarray of [ar1], or if [off2] and [len]
83 do not designate a valid subarray of [ar2].*)
86 (** {6 Weak hash tables} *)
88 (** A weak hash table is a hashed set of values. Each value may
89 magically disappear from the set when it is not used by the
90 rest of the program any more. This is normally used to share
91 data structures without inducing memory leaks.
92 Weak hash tables are defined on values from a {!Hashtbl.HashedType}
93 module; the [equal] relation and [hash] function are taken from that
94 module. We will say that [v] is an instance of [x] if [equal x v]
95 is [true].
97 The [equal] relation must be able to work on a shallow copy of
98 the values and give the same result as with the values themselves.
101 module type S = sig
102 type data
103 (** The type of the elements stored in the table. *)
104 type t
105 (** The type of tables that contain elements of type [data].
106 Note that weak hash tables cannot be marshaled using
107 {!Pervasives.output_value} or the functions of the {!Marshal}
108 module. *)
109 val create : int -> t
110 (** [create n] creates a new empty weak hash table, of initial
111 size [n]. The table will grow as needed. *)
112 val clear : t -> unit
113 (** Remove all elements from the table. *)
114 val merge : t -> data -> data
115 (** [merge t x] returns an instance of [x] found in [t] if any,
116 or else adds [x] to [t] and return [x]. *)
117 val add : t -> data -> unit
118 (** [add t x] adds [x] to [t]. If there is already an instance
119 of [x] in [t], it is unspecified which one will be
120 returned by subsequent calls to [find] and [merge]. *)
121 val remove : t -> data -> unit
122 (** [remove t x] removes from [t] one instance of [x]. Does
123 nothing if there is no instance of [x] in [t]. *)
124 val find : t -> data -> data
125 (** [find t x] returns an instance of [x] found in [t].
126 Raise [Not_found] if there is no such element. *)
127 val find_all : t -> data -> data list
128 (** [find_all t x] returns a list of all the instances of [x]
129 found in [t]. *)
130 val mem : t -> data -> bool
131 (** [mem t x] returns [true] if there is at least one instance
132 of [x] in [t], false otherwise. *)
133 val iter : (data -> unit) -> t -> unit
134 (** [iter f t] calls [f] on each element of [t], in some unspecified
135 order. It is not specified what happens if [f] tries to change
136 [t] itself. *)
137 val fold : (data -> 'a -> 'a) -> t -> 'a -> 'a
138 (** [fold f t init] computes [(f d1 (... (f dN init)))] where
139 [d1 ... dN] are the elements of [t] in some unspecified order.
140 It is not specified what happens if [f] tries to change [t]
141 itself. *)
142 val count : t -> int
143 (** Count the number of elements in the table. [count t] gives the
144 same result as [fold (fun _ n -> n+1) t 0] but does not delay the
145 deallocation of the dead elements. *)
146 val stats : t -> int * int * int * int * int * int
147 (** Return statistics on the table. The numbers are, in order:
148 table length, number of entries, sum of bucket lengths,
149 smallest bucket length, median bucket length, biggest bucket length. *)
150 end;;
151 (** The output signature of the functor {!Weak.Make}. *)
153 module Make (H : Hashtbl.HashedType) : S with type data = H.t;;
154 (** Functor building an implementation of the weak hash table structure. *)