]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/otherlibs/dbm/dbm.mli
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / otherlibs / dbm / dbm.mli
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*          Francois Rouaix, projet Cristal, INRIA Rocquencourt        *)
6 (*                                                                     *)
7 (*  Copyright 1996 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: dbm.mli 4144 2001-12-07 13:41:02Z xleroy $ *)
15
16 (** Interface to the NDBM database. *)
17
18 type t
19 (** The type of file descriptors opened on NDBM databases. *)
20
21
22 type open_flag = 
23     Dbm_rdonly
24   | Dbm_wronly
25   | Dbm_rdwr
26   | Dbm_create
27 (** Flags for opening a database (see {!Dbm.opendbm}). *)
28
29
30 exception Dbm_error of string
31 (** Raised by the following functions when an error is encountered. *)
32
33 val opendbm : string -> open_flag list -> int -> t
34 (** Open a descriptor on an NDBM database. The first argument is
35    the name of the database (without the [.dir] and [.pag] suffixes).
36    The second argument is a list of flags: [Dbm_rdonly] opens
37    the database for reading only, [Dbm_wronly] for writing only,
38    [Dbm_rdwr] for reading and writing; [Dbm_create] causes the
39    database to be created if it does not already exist.
40    The third argument is the permissions to give to the database
41    files, if the database is created. *)
42
43 external close : t -> unit = "caml_dbm_close"
44 (** Close the given descriptor. *)
45
46 external find : t -> string -> string = "caml_dbm_fetch"
47 (** [find db key] returns the data associated with the given
48    [key] in the database opened for the descriptor [db].
49    Raise [Not_found] if the [key] has no associated data. *)
50
51 external add : t -> string -> string -> unit = "caml_dbm_insert"
52 (** [add db key data] inserts the pair ([key], [data]) in
53    the database [db]. If the database already contains data
54    associated with [key], raise [Dbm_error "Entry already exists"]. *)
55
56 external replace : t -> string -> string -> unit = "caml_dbm_replace"
57 (** [replace db key data] inserts the pair ([key], [data]) in
58    the database [db]. If the database already contains data
59    associated with [key], that data is discarded and silently
60    replaced by the new [data]. *)
61
62 external remove : t -> string -> unit = "caml_dbm_delete"
63 (** [remove db key data] removes the data associated with [key]
64    in [db]. If [key] has no associated data, raise
65    [Dbm_error "dbm_delete"]. *)
66
67 external firstkey : t -> string = "caml_dbm_firstkey"
68 (** See {!Dbm.nextkey}.*)
69
70 external nextkey : t -> string = "caml_dbm_nextkey"
71 (** Enumerate all keys in the given database, in an unspecified order.
72    [firstkey db] returns the first key, and repeated calls
73    to [nextkey db] return the remaining keys. [Not_found] is raised
74    when all keys have been enumerated. *)
75
76 val iter : (string -> string -> 'a) -> t -> unit
77 (** [iter f db] applies [f] to each ([key], [data]) pair in
78    the database [db]. [f] receives [key] as first argument
79    and [data] as second argument. *)
80