]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/stdlib/weak.mli
Inital import
[l4.git] / l4 / pkg / ocaml / contrib / stdlib / weak.mli
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 (***********************************************************************)
13
14 (* $Id: weak.mli 9130 2008-11-13 10:39:46Z doligez $ *)
15
16 (** Arrays of weak pointers and hash tables of weak pointers. *)
17
18
19 (** {6 Low-level functions} *)
20
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 whenever
24    the value is not used any more (through normal pointers) by the
25    program.  Note that finalisation functions are run after the
26    weak pointers are erased.
27  
28    A weak pointer is said to be full if it points to a value,
29    empty if the value was erased by the GC.
30
31    Notes:
32    - Integers are not allocated and cannot be stored in weak arrays.
33    - Weak arrays cannot be marshaled using {!Pervasives.output_value}
34      nor the functions of the {!Marshal} module.
35 *)
36
37
38 val create : int -> 'a t
39 (** [Weak.create n] returns a new weak array of length [n].
40    All the pointers are initially empty.  Raise [Invalid_argument]
41    if [n] is negative or greater than {!Sys.max_array_length}[-1].*)
42
43 val length : 'a t -> int
44 (** [Weak.length ar] returns the length (number of elements) of
45    [ar].*)
46
47 val set : 'a t -> int -> 'a option -> unit
48 (** [Weak.set ar n (Some el)] sets the [n]th cell of [ar] to be a
49    (full) pointer to [el]; [Weak.set ar n None] sets the [n]th
50    cell of [ar] to empty.
51    Raise [Invalid_argument "Weak.set"] if [n] is not in the range
52    0 to {!Weak.length}[ a - 1].*)
53
54 val get : 'a t -> int -> 'a option
55 (** [Weak.get ar n] returns None if the [n]th cell of [ar] is
56    empty, [Some x] (where [x] is the value) if it is full.
57    Raise [Invalid_argument "Weak.get"] if [n] is not in the range
58    0 to {!Weak.length}[ a - 1].*)
59
60 val get_copy : 'a t -> int -> 'a option
61 (** [Weak.get_copy ar n] returns None if the [n]th cell of [ar] is
62    empty, [Some x] (where [x] is a (shallow) copy of the value) if
63    it is full.
64    In addition to pitfalls with mutable values, the interesting
65    difference with [get] is that [get_copy] does not prevent
66    the incremental GC from erasing the value in its current cycle
67    ([get] may delay the erasure to the next GC cycle).
68    Raise [Invalid_argument "Weak.get"] if [n] is not in the range
69    0 to {!Weak.length}[ a - 1].*)
70
71
72 val check : 'a t -> int -> bool
73 (** [Weak.check ar n] returns [true] if the [n]th cell of [ar] is
74    full, [false] if it is empty.  Note that even if [Weak.check ar n]
75    returns [true], a subsequent {!Weak.get}[ ar n] can return [None].*)
76
77 val fill : 'a t -> int -> int -> 'a option -> unit
78 (** [Weak.fill ar ofs len el] sets to [el] all pointers of [ar] from
79    [ofs] to [ofs + len - 1].  Raise [Invalid_argument "Weak.fill"]
80    if [ofs] and [len] do not designate a valid subarray of [a].*)
81
82 val blit : 'a t -> int -> 'a t -> int -> int -> unit
83 (** [Weak.blit ar1 off1 ar2 off2 len] copies [len] weak pointers
84    from [ar1] (starting at [off1]) to [ar2] (starting at [off2]).
85    It works correctly even if [ar1] and [ar2] are the same.
86    Raise [Invalid_argument "Weak.blit"] if [off1] and [len] do
87    not designate a valid subarray of [ar1], or if [off2] and [len]
88    do not designate a valid subarray of [ar2].*)
89
90
91 (** {6 Weak hash tables} *)
92
93 (** A weak hash table is a hashed set of values.  Each value may
94     magically disappear from the set when it is not used by the
95     rest of the program any more.  This is normally used to share
96     data structures without inducing memory leaks.
97     Weak hash tables are defined on values from a {!Hashtbl.HashedType}
98     module; the [equal] relation and [hash] function are taken from that
99     module.  We will say that [v] is an instance of [x] if [equal x v]
100     is [true].
101
102     The [equal] relation must be able to work on a shallow copy of
103     the values and give the same result as with the values themselves.
104     *)
105
106 module type S = sig
107   type data
108     (** The type of the elements stored in the table. *)
109   type t
110     (** The type of tables that contain elements of type [data].
111         Note that weak hash tables cannot be marshaled using
112         {!Pervasives.output_value} or the functions of the {!Marshal}
113         module. *)
114   val create : int -> t
115     (** [create n] creates a new empty weak hash table, of initial
116         size [n].  The table will grow as needed. *)
117   val clear : t -> unit
118     (** Remove all elements from the table. *)
119   val merge : t -> data -> data
120     (** [merge t x] returns an instance of [x] found in [t] if any,
121         or else adds [x] to [t] and return [x]. *)
122   val add : t -> data -> unit
123     (** [add t x] adds [x] to [t].  If there is already an instance
124         of [x] in [t], it is unspecified which one will be
125         returned by subsequent calls to [find] and [merge]. *)
126   val remove : t -> data -> unit
127     (** [remove t x] removes from [t] one instance of [x].  Does
128         nothing if there is no instance of [x] in [t]. *)
129   val find : t -> data -> data
130     (** [find t x] returns an instance of [x] found in [t].
131         Raise [Not_found] if there is no such element. *)
132   val find_all : t -> data -> data list
133     (** [find_all t x] returns a list of all the instances of [x]
134         found in [t]. *)
135   val mem : t -> data -> bool
136     (** [mem t x] returns [true] if there is at least one instance
137         of [x] in [t], false otherwise. *)
138   val iter : (data -> unit) -> t -> unit
139     (** [iter f t] calls [f] on each element of [t], in some unspecified
140         order.  It is not specified what happens if [f] tries to change
141         [t] itself. *)
142   val fold : (data -> 'a -> 'a) -> t -> 'a -> 'a
143     (** [fold f t init] computes [(f d1 (... (f dN init)))] where
144         [d1 ... dN] are the elements of [t] in some unspecified order.
145         It is not specified what happens if [f] tries to change [t]
146         itself. *)
147   val count : t -> int
148     (** Count the number of elements in the table.  [count t] gives the
149         same result as [fold (fun _ n -> n+1) t 0] but does not delay the
150         deallocation of the dead elements. *)
151   val stats : t -> int * int * int * int * int * int
152     (** Return statistics on the table.  The numbers are, in order:
153         table length, number of entries, sum of bucket lengths,
154         smallest bucket length, median bucket length, biggest bucket length. *)
155 end;;
156 (** The output signature of the functor {!Weak.Make}. *)
157
158 module Make (H : Hashtbl.HashedType) : S with type data = H.t;;
159 (** Functor building an implementation of the weak hash table structure. *)