1996-06-12 06:54:53 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
|
|
|
(* Objective Caml *)
|
|
|
|
(* *)
|
|
|
|
(* Francois Rouaix, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
|
|
|
(* under the terms of the GNU Library General Public License. *)
|
1996-06-12 06:54:53 -07:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
1996-05-15 07:18:46 -07:00
|
|
|
type t
|
|
|
|
|
1996-05-30 04:11:07 -07:00
|
|
|
type open_flag =
|
|
|
|
Dbm_rdonly | Dbm_wronly | Dbm_rdwr | Dbm_create
|
|
|
|
|
1996-05-15 07:18:46 -07:00
|
|
|
type dbm_flag =
|
|
|
|
DBM_INSERT
|
|
|
|
| DBM_REPLACE
|
|
|
|
|
|
|
|
exception Dbm_error of string
|
|
|
|
|
1998-06-01 04:42:57 -07:00
|
|
|
external raw_opendbm : string -> open_flag list -> int -> t
|
1997-05-19 08:42:21 -07:00
|
|
|
= "caml_dbm_open"
|
1998-06-01 04:42:57 -07:00
|
|
|
|
|
|
|
let opendbm file flags mode =
|
|
|
|
try
|
|
|
|
raw_opendbm file flags mode
|
|
|
|
with Dbm_error msg ->
|
|
|
|
raise(Dbm_error("Can't open file " ^ file))
|
|
|
|
|
|
|
|
(* By exporting opendbm as val, we are sure to link in this
|
1997-07-15 07:31:29 -07:00
|
|
|
file (we must register the exception). Since t is abstract, programs
|
|
|
|
have to call it in order to do anything *)
|
|
|
|
|
1996-05-15 07:18:46 -07:00
|
|
|
external close : t -> unit = "caml_dbm_close"
|
1996-06-10 05:09:41 -07:00
|
|
|
external find : t -> string -> string = "caml_dbm_fetch"
|
|
|
|
external add : t -> string -> string -> unit = "caml_dbm_insert"
|
|
|
|
external replace : t -> string -> string -> unit = "caml_dbm_replace"
|
|
|
|
external remove : t -> string -> unit = "caml_dbm_delete"
|
1996-05-15 07:18:46 -07:00
|
|
|
external firstkey : t -> string = "caml_dbm_firstkey"
|
|
|
|
external nextkey : t -> string = "caml_dbm_nextkey"
|
|
|
|
|
1997-07-15 07:31:29 -07:00
|
|
|
let _ = Callback.register_exception "dbmerror" (Dbm_error "")
|
1996-05-15 07:18:46 -07:00
|
|
|
|
1996-06-10 05:09:41 -07:00
|
|
|
(* Usual iterator *)
|
1996-05-15 07:18:46 -07:00
|
|
|
let iter f t =
|
2000-04-02 19:21:07 -07:00
|
|
|
let rec walk = function
|
|
|
|
None -> ()
|
|
|
|
| Some k ->
|
|
|
|
f k (find t k);
|
|
|
|
walk (try Some(nextkey t) with Not_found -> None)
|
1996-05-15 07:18:46 -07:00
|
|
|
in
|
2000-04-02 19:21:07 -07:00
|
|
|
walk (try Some(firstkey t) with Not_found -> None)
|