1997-02-24 11:24:39 -08:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
|
|
|
(* Objective Caml *)
|
|
|
|
(* *)
|
1997-02-25 06:39:02 -08:00
|
|
|
(* Damien Doligez, projet Para, INRIA Rocquencourt *)
|
1997-02-24 11:24:39 -08:00
|
|
|
(* *)
|
1997-02-25 06:39:02 -08:00
|
|
|
(* Copyright 1997 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
2001-12-07 05:41:02 -08:00
|
|
|
(* under the terms of the GNU Library General Public License, with *)
|
|
|
|
(* the special exception on linking described in file ../LICENSE. *)
|
1997-02-24 11:24:39 -08:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
2001-10-26 16:33:00 -07:00
|
|
|
(** Arrays of weak pointers. *)
|
1997-02-24 11:24:39 -08:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
type 'a t
|
2001-10-26 16:33:00 -07:00
|
|
|
(** The type of arrays of weak pointers (weak arrays). A weak
|
|
|
|
pointer is a value that the garbage collector may erase at
|
|
|
|
any time.
|
|
|
|
A weak pointer is said to be full if it points to a value,
|
|
|
|
empty if the value was erased by the GC.*)
|
1997-02-24 11:24:39 -08:00
|
|
|
|
2001-10-26 16:33:00 -07:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val create : int -> 'a t
|
2001-10-26 16:33:00 -07:00
|
|
|
(** [Weak.create n] returns a new weak array of length [n].
|
|
|
|
All the pointers are initially empty. Raise [Invalid_argument]
|
|
|
|
if [n] is negative or greater than {!Sys.max_array_length}[-1].*)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val length : 'a t -> int
|
2001-10-26 16:33:00 -07:00
|
|
|
(** [Weak.length ar] returns the length (number of elements) of
|
|
|
|
[ar].*)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val set : 'a t -> int -> 'a option -> unit
|
2001-10-26 16:33:00 -07:00
|
|
|
(** [Weak.set ar n (Some el)] sets the [n]th cell of [ar] to be a
|
|
|
|
(full) pointer to [el]; [Weak.set ar n None] sets the [n]th
|
|
|
|
cell of [ar] to empty.
|
|
|
|
Raise [Invalid_argument "Weak.set"] if [n] is not in the range
|
|
|
|
0 to {!Weak.length}[ a - 1].*)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val get : 'a t -> int -> 'a option
|
2001-10-26 16:33:00 -07:00
|
|
|
(** [Weak.get ar n] returns None if the [n]th cell of [ar] is
|
|
|
|
empty, [Some x] (where [x] is the value) if it is full.
|
|
|
|
Raise [Invalid_argument "Weak.get"] if [n] is not in the range
|
|
|
|
0 to {!Weak.length}[ a - 1].*)
|
2000-08-23 10:10:41 -07:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val get_copy : 'a t -> int -> 'a option
|
2001-10-26 16:33:00 -07:00
|
|
|
(** [Weak.get_copy ar n] returns None if the [n]th cell of [ar] is
|
|
|
|
empty, [Some x] (where [x] is a (shallow) copy of the value) if
|
|
|
|
it is full.
|
|
|
|
In addition to pitfalls with mutable values, the interesting
|
|
|
|
difference with [get] is that [get_copy] does not prevent
|
|
|
|
the incremental GC from erasing the value in its current cycle
|
|
|
|
([get] may delay the erasure to the next GC cycle).
|
|
|
|
Raise [Invalid_argument "Weak.get"] if [n] is not in the range
|
|
|
|
0 to {!Weak.length}[ a - 1].*)
|
2000-08-23 10:10:41 -07:00
|
|
|
|
2001-10-26 16:33:00 -07:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val check : 'a t -> int -> bool
|
2001-10-26 16:33:00 -07:00
|
|
|
(** [Weak.check ar n] returns [true] if the [n]th cell of [ar] is
|
|
|
|
full, [false] if it is empty. Note that even if [Weak.check ar n]
|
|
|
|
returns [true], a subsequent {!Weak.get}[ ar n] can return [None].*)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val fill : 'a t -> int -> int -> 'a option -> unit
|
2001-10-26 16:33:00 -07:00
|
|
|
(** [Weak.fill ar ofs len el] sets to [el] all pointers of [ar] from
|
|
|
|
[ofs] to [ofs + len - 1]. Raise [Invalid_argument "Weak.fill"]
|
|
|
|
if [ofs] and [len] do not designate a valid subarray of [a].*)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val blit : 'a t -> int -> 'a t -> int -> int -> unit
|
2001-10-26 16:33:00 -07:00
|
|
|
(** [Weak.blit ar1 off1 ar2 off2 len] copies [len] weak pointers
|
|
|
|
from [ar1] (starting at [off1]) to [ar2] (starting at [off2]).
|
|
|
|
It works correctly even if [ar1] and [ar2] are the same.
|
|
|
|
Raise [Invalid_argument "Weak.blit"] if [off1] and [len] do
|
|
|
|
not designate a valid subarray of [ar1], or if [off2] and [len]
|
|
|
|
do not designate a valid subarray of [ar2].*)
|
|
|
|
|