summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorFrancois Rouaix <francois.rouaix@gmail.com>1996-06-10 12:09:41 +0000
committerFrancois Rouaix <francois.rouaix@gmail.com>1996-06-10 12:09:41 +0000
commitdbf5cb6bb94f0577c54d26ca565980419bb0734a (patch)
treef644035980f2e63f870fdde1145f6ac70725f642
parentc5bbe9955115f964e4653199a13c293423f5e44f (diff)
Changed REPLACE/INSERT encoding
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@868 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--otherlibs/dbm/dbm.c34
-rw-r--r--otherlibs/dbm/dbm.ml16
-rw-r--r--otherlibs/dbm/dbm.mli18
3 files changed, 35 insertions, 33 deletions
diff --git a/otherlibs/dbm/dbm.c b/otherlibs/dbm/dbm.c
index e23f31706..b83f13f90 100644
--- a/otherlibs/dbm/dbm.c
+++ b/otherlibs/dbm/dbm.c
@@ -11,10 +11,6 @@ static int dbm_open_flags[] = {
O_RDONLY, O_WRONLY, O_RDWR, O_CREAT
};
-static int dbm_flag_table[] = {
- DBM_INSERT, DBM_REPLACE
-};
-
/* Exception bucket for DBMError */
static value dbm_exn;
value caml_dbm_install_exn(bucket) /* ML */
@@ -73,10 +69,9 @@ value caml_dbm_fetch(vdb,vkey) /* ML */
else raise_not_found();
}
-value caml_dbm_store(vdb,vkey,vcontent,vflags) /* ML */
- value vdb,vkey,vcontent,vflags;
+value caml_dbm_insert(vdb,vkey,vcontent) /* ML */
+ value vdb,vkey,vcontent;
{
- int flags = convert_flag_list(vflags, dbm_flag_table);
datum key, content;
key.dptr = String_val(vkey);
@@ -84,13 +79,32 @@ value caml_dbm_store(vdb,vkey,vcontent,vflags) /* ML */
content.dptr = String_val(vcontent);
content.dsize = string_length(vcontent);
- switch(dbm_store((DBM *)vdb, key, content, flags)) {
+ switch(dbm_store((DBM *)vdb, key, content, DBM_INSERT)) {
case 0:
return Val_unit;
case 1: /* DBM_INSERT and already existing */
- failwith("dbm_store");
+ raise_dbm("Entry already exists");
+ default:
+ raise_dbm("dbm_store failed");
+ }
+}
+
+
+value caml_dbm_replace(vdb,vkey,vcontent) /* ML */
+ value vdb,vkey,vcontent;
+{
+ datum key, content;
+
+ key.dptr = String_val(vkey);
+ key.dsize = string_length(vkey);
+ content.dptr = String_val(vcontent);
+ content.dsize = string_length(vcontent);
+
+ switch(dbm_store((DBM *)vdb, key, content, DBM_REPLACE)) {
+ case 0:
+ return Val_unit;
default:
- raise_dbm("dbm_store");
+ raise_dbm("dbm_store failed");
}
}
diff --git a/otherlibs/dbm/dbm.ml b/otherlibs/dbm/dbm.ml
index 06ec71f62..e39e4c656 100644
--- a/otherlibs/dbm/dbm.ml
+++ b/otherlibs/dbm/dbm.ml
@@ -14,23 +14,19 @@ external install_exn : exn -> unit
external opendbm : string -> open_flag list -> int -> t
= "caml_dbm_open"
external close : t -> unit = "caml_dbm_close"
-external fetch : t -> string -> string = "caml_dbm_fetch"
-external store : t -> string -> string -> dbm_flag list -> unit
- = "caml_dbm_store"
-external delete : t -> string -> unit = "caml_dbm_delete"
+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"
external firstkey : t -> string = "caml_dbm_firstkey"
external nextkey : t -> string = "caml_dbm_nextkey"
let _ = install_exn (Dbm_error "")
-(* Usual interfaces *)
-let add t x v = store t x v [DBM_INSERT]
-let find = fetch
-let remove = delete
-
+(* Usual iterator *)
let iter f t =
let rec walk k =
- f k (fetch t k);
+ f k (find t k);
match try Some(nextkey t) with Not_found -> None
with
None -> ()
diff --git a/otherlibs/dbm/dbm.mli b/otherlibs/dbm/dbm.mli
index 1c1b1f632..8fb9dfa67 100644
--- a/otherlibs/dbm/dbm.mli
+++ b/otherlibs/dbm/dbm.mli
@@ -5,25 +5,17 @@ type t
type open_flag =
Dbm_rdonly | Dbm_wronly | Dbm_rdwr | Dbm_create
-type dbm_flag =
- DBM_INSERT
- | DBM_REPLACE
-
exception Dbm_error of string
external opendbm : string -> open_flag list -> int -> t
= "caml_dbm_open"
external close : t -> unit = "caml_dbm_close"
-external fetch : t -> string -> string = "caml_dbm_fetch"
-external store : t -> string -> string -> dbm_flag list -> unit
- = "caml_dbm_store"
-external delete : t -> string -> unit = "caml_dbm_delete"
+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"
external firstkey : t -> string = "caml_dbm_firstkey"
external nextkey : t -> string = "caml_dbm_nextkey"
-
-(* Usual interfaces *)
-val add: t -> string -> string -> unit
-val find : t -> string -> string
-val remove : t -> string -> unit
+(* Usual iterator *)
val iter : (string -> string -> 'a) -> t -> unit