summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>2011-12-17 10:45:23 +0000
committerXavier Leroy <xavier.leroy@inria.fr>2011-12-17 10:45:23 +0000
commit9178181eae1aa03d8d2ef2ab823a80f208c408a8 (patch)
treeb45f0f5844205f56a0bdfa6d623d645a7c869040
parent4db01f01b6157201fb9f7baf5cf2c7ec805a3e78 (diff)
The "DBM" library (interface with Unix DBM key-value stores) is no
longer part of this distribution. It now lives its own life at https://forge.ocamlcore.org/projects/camldbm/. Bye bye, DBM. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@11881 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--Changes8
-rw-r--r--Makefile2
-rwxr-xr-xboot/ocamlcbin1164552 -> 1165279 bytes
-rwxr-xr-xboot/ocamldepbin313141 -> 313120 bytes
-rwxr-xr-xboot/ocamllexbin171518 -> 171511 bytes
-rw-r--r--config/Makefile-templ7
-rwxr-xr-xconfigure48
-rw-r--r--myocamlbuild.ml4
-rw-r--r--myocamlbuild_config.mli2
-rw-r--r--otherlibs/dbm/.depend3
-rw-r--r--otherlibs/dbm/Makefile32
-rw-r--r--otherlibs/dbm/cldbm.c166
-rw-r--r--otherlibs/dbm/dbm.ml58
-rw-r--r--otherlibs/dbm/dbm.mli79
-rw-r--r--otherlibs/dbm/libmldbm.clib1
15 files changed, 9 insertions, 401 deletions
diff --git a/Changes b/Changes
index c274ee638..7055f1152 100644
--- a/Changes
+++ b/Changes
@@ -2,7 +2,6 @@ OCaml 3.13.0:
-------------
- The official name of the language is now OCaml.
-- Warning 28 is now enabled by default.
Language features:
- Added Generalized Abstract Data Types (GADTs) to the language. See
@@ -17,6 +16,7 @@ Language features:
Compilers:
- Revised simplification of let-alias (PR#5205, PR#5288)
- Better reporting of compiler version mismatch in .cmi files
+- Warning 28 is now enabled by default.
Native-code compiler:
- Optimized handling of partially-applied functions (PR#5287)
@@ -40,6 +40,12 @@ Feature wishes:
- PR#5411: new directive for the toplevel: #load_rec
- PR#5420: Unix.openfile share mode (Windows)
+Shedding weight:
+- The "DBM" library (interface with Unix DBM key-value stores) is no
+ longer part of this distribution. It now lives its own life at
+ https://forge.ocamlcore.org/projects/camldbm/
+
+
OCaml 3.12.1:
----------------------
diff --git a/Makefile b/Makefile
index 94c069f60..a8f442e52 100644
--- a/Makefile
+++ b/Makefile
@@ -280,7 +280,7 @@ install:
if test -d $(MANDIR)/man$(MANEXT); then : ; \
else $(MKDIR) $(MANDIR)/man$(MANEXT); fi
cd $(LIBDIR); rm -f dllbigarray.so dlllabltk.so dllnums.so \
- dllthreads.so dllunix.so dllgraphics.so dllmldbm.so dllstr.so \
+ dllthreads.so dllunix.so dllgraphics.so dllstr.so \
dlltkanim.so
cd byterun; $(MAKE) install
cp ocamlc $(BINDIR)/ocamlc$(EXE)
diff --git a/boot/ocamlc b/boot/ocamlc
index 066862f66..cfdab35ed 100755
--- a/boot/ocamlc
+++ b/boot/ocamlc
Binary files differ
diff --git a/boot/ocamldep b/boot/ocamldep
index 92b3df8f4..d8d13c565 100755
--- a/boot/ocamldep
+++ b/boot/ocamldep
Binary files differ
diff --git a/boot/ocamllex b/boot/ocamllex
index 52e01fce9..4e943e832 100755
--- a/boot/ocamllex
+++ b/boot/ocamllex
Binary files differ
diff --git a/config/Makefile-templ b/config/Makefile-templ
index da20a75fb..cd619c45c 100644
--- a/config/Makefile-templ
+++ b/config/Makefile-templ
@@ -268,13 +268,6 @@ BNG_ASM_LEVEL=1
# For SunOS with OpenLook:
#X11_LINK=-L$(X11_LIB) -lX11
-### -I options for finding the include file ndbm.h
-# Needed for the "dbm" package
-# Usually:
-#DBM_INCLUDES=
-# For recent Linux systems:
-#DBM_INCLUDES=-I/usr/include/gdbm
-
### Preprocessor options for finding tcl.h and tk.h
# Needed for the "labltk" package
# Required only if not in the standard include path.
diff --git a/configure b/configure
index 8ec85a624..3471df645 100755
--- a/configure
+++ b/configure
@@ -1393,54 +1393,6 @@ fi
echo "X11_INCLUDES=$x11_include" >> Makefile
echo "X11_LINK=$x11_link" >> Makefile
-# See if we can compile the dbm library
-
-dbm_include="not found"
-dbm_link="not found"
-use_gdbm_ndbm=no
-
-for dir in /usr/include /usr/include/db1 /usr/include/gdbm; do
- if test -f $dir/ndbm.h; then
- dbm_include=$dir
- if sh ./hasgot dbm_open; then
- dbm_link=""
- elif sh ./hasgot -lndbm dbm_open; then
- dbm_link="-lndbm"
- elif sh ./hasgot -ldb1 dbm_open; then
- dbm_link="-ldb1"
- elif sh ./hasgot -lgdbm dbm_open; then
- dbm_link="-lgdbm"
- elif sh ./hasgot -lgdbm_compat -lgdbm dbm_open; then
- dbm_link="-lgdbm_compat -lgdbm"
- fi
- break
- fi
- if test -f $dir/gdbm-ndbm.h; then
- dbm_include=$dir
- use_gdbm_ndbm=yes
- if sh ./hasgot -lgdbm_compat -lgdbm dbm_open; then
- dbm_link="-lgdbm_compat -lgdbm"
- fi
- break
- fi
-done
-if test "$dbm_include" = "not found" || test "$dbm_link" = "not found"; then
- echo "NDBM not found, the \"dbm\" library will not be supported."
-else
- echo "NDBM found (in $dbm_include)"
- if test "$dbm_include" = "/usr/include"; then
- dbm_include=""
- else
- dbm_include="-I$dbm_include"
- fi
- if test "$use_gdbm_ndbm" = "yes"; then
- echo "#define DBM_USES_GDBM_NDBM" >> s.h
- fi
- otherlibraries="$otherlibraries dbm"
-fi
-echo "DBM_INCLUDES=$dbm_include" >> Makefile
-echo "DBM_LINK=$dbm_link" >> Makefile
-
# Look for tcl/tk
echo "Configuring LablTk..."
diff --git a/myocamlbuild.ml b/myocamlbuild.ml
index 59944955c..449fc59c8 100644
--- a/myocamlbuild.ml
+++ b/myocamlbuild.ml
@@ -289,7 +289,7 @@ Pathname.define_context "ocamlbuild" ["ocamlbuild"; "stdlib"; "."];;
Pathname.define_context "lex" ["lex"; "stdlib"];;
List.iter (fun x -> let x = "otherlibs"/x in Pathname.define_context x [x; "stdlib"])
- ["bigarray"; "dbm"; "graph"; "num"; "str"; "systhreads"; "unix"; "win32graph"; "win32unix"];;
+ ["bigarray"; "graph"; "num"; "str"; "systhreads"; "unix"; "win32graph"; "win32unix"];;
(* The bootstrap standard library *)
copy_rule "The bootstrap standard library" "stdlib/%" "boot/%";;
@@ -407,8 +407,6 @@ flag ["c"; "compile"; "otherlibs_bigarray"] (S[A"-I"; P"../otherlibs/bigarray"])
flag [(* "ocaml" or "c"; *) "ocamlmklib"; "otherlibs_graph"] (S[Sh C.x11_link]);;
flag ["c"; "compile"; "otherlibs_graph"] (S[Sh C.x11_includes; A"-I../otherlibs/graph"]);;
flag ["c"; "compile"; "otherlibs_win32graph"] (A"-I../otherlibs/win32graph");;
-flag ["c"; "compile"; "otherlibs_dbm"] (Sh C.dbm_includes);;
-flag [(* "ocaml" oc "c"; *) "ocamlmklib"; "otherlibs_dbm"] (S[A"-oc"; A"otherlibs/dbm/mldbm"; Sh C.dbm_link]);;
flag ["ocaml"; "ocamlmklib"; "otherlibs_threads"] (S[A"-oc"; A"otherlibs/threads/vmthreads"]);;
flag ["c"; "compile"; "otherlibs_num"] begin
S[A("-DBNG_ARCH_"^C.bng_arch);
diff --git a/myocamlbuild_config.mli b/myocamlbuild_config.mli
index c50049956..3345a5701 100644
--- a/myocamlbuild_config.mli
+++ b/myocamlbuild_config.mli
@@ -23,8 +23,6 @@ val pthread_link : string
val x11_includes : string
val x11_link : string
val tk_link : string
-val dbm_includes : string
-val dbm_link : string
val bytecc : string
val bytecccompopts : string
val bytecclinkopts : string
diff --git a/otherlibs/dbm/.depend b/otherlibs/dbm/.depend
deleted file mode 100644
index 4e5750fa4..000000000
--- a/otherlibs/dbm/.depend
+++ /dev/null
@@ -1,3 +0,0 @@
-dbm.cmi:
-dbm.cmo: dbm.cmi
-dbm.cmx: dbm.cmi
diff --git a/otherlibs/dbm/Makefile b/otherlibs/dbm/Makefile
deleted file mode 100644
index dcd068ade..000000000
--- a/otherlibs/dbm/Makefile
+++ /dev/null
@@ -1,32 +0,0 @@
-#########################################################################
-# #
-# OCaml #
-# #
-# Xavier Leroy, projet Cristal, INRIA Rocquencourt #
-# #
-# Copyright 1999 Institut National de Recherche en Informatique et #
-# en Automatique. All rights reserved. This file is distributed #
-# under the terms of the GNU Library General Public License, with #
-# the special exception on linking described in file ../../LICENSE. #
-# #
-#########################################################################
-
-# $Id$
-
-# Makefile for the ndbm library
-
-LIBNAME=dbm
-CLIBNAME=mldbm
-CAMLOBJS=dbm.cmo
-COBJS=cldbm.o
-EXTRACFLAGS=$(DBM_INCLUDES)
-LINKOPTS=$(DBM_LINK)
-LDOPTS=-ldopt "$(DBM_LINK)"
-
-include ../Makefile
-
-
-depend:
- ../../boot/ocamlrun ../../tools/ocamldep *.mli *.ml > .depend
-
-include .depend
diff --git a/otherlibs/dbm/cldbm.c b/otherlibs/dbm/cldbm.c
deleted file mode 100644
index 6c9954a34..000000000
--- a/otherlibs/dbm/cldbm.c
+++ /dev/null
@@ -1,166 +0,0 @@
-/***********************************************************************/
-/* */
-/* OCaml */
-/* */
-/* Francois Rouaix, projet Cristal, INRIA Rocquencourt */
-/* */
-/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* en Automatique. All rights reserved. This file is distributed */
-/* under the terms of the GNU Library General Public License, with */
-/* the special exception on linking described in file ../../LICENSE. */
-/* */
-/***********************************************************************/
-
-/* $Id$ */
-
-#include <string.h>
-#include <fcntl.h>
-#include <mlvalues.h>
-#include <alloc.h>
-#include <memory.h>
-#include <fail.h>
-#include <callback.h>
-
-#ifdef DBM_USES_GDBM_NDBM
-#include <gdbm-ndbm.h>
-#else
-#include <ndbm.h>
-#endif
-
-/* Quite close to sys_open_flags, but we need RDWR */
-static int dbm_open_flags[] = {
- O_RDONLY, O_WRONLY, O_RDWR, O_CREAT
-};
-
-static void raise_dbm (char *errmsg) Noreturn;
-
-static void raise_dbm(char *errmsg)
-{
- static value * dbm_exn = NULL;
- if (dbm_exn == NULL)
- dbm_exn = caml_named_value("dbmerror");
- raise_with_string(*dbm_exn, errmsg);
-}
-
-#define DBM_val(v) *((DBM **) &Field(v, 0))
-
-static value alloc_dbm(DBM * db)
-{
- value res = alloc_small(1, Abstract_tag);
- DBM_val(res) = db;
- return res;
-}
-
-static DBM * extract_dbm(value vdb)
-{
- if (DBM_val(vdb) == NULL) raise_dbm("DBM has been closed");
- return DBM_val(vdb);
-}
-
-/* Dbm.open : string -> Sys.open_flag list -> int -> t */
-value caml_dbm_open(value vfile, value vflags, value vmode) /* ML */
-{
- char *file = String_val(vfile);
- int flags = convert_flag_list(vflags, dbm_open_flags);
- int mode = Int_val(vmode);
- DBM *db = dbm_open(file,flags,mode);
-
- if (db == NULL)
- raise_dbm("Can't open file");
- else
- return (alloc_dbm(db));
-}
-
-/* Dbm.close: t -> unit */
-value caml_dbm_close(value vdb) /* ML */
-{
- dbm_close(extract_dbm(vdb));
- DBM_val(vdb) = NULL;
- return Val_unit;
-}
-
-/* Dbm.fetch: t -> string -> string */
-value caml_dbm_fetch(value vdb, value vkey) /* ML */
-{
- datum key,answer;
- key.dptr = String_val(vkey);
- key.dsize = string_length(vkey);
- answer = dbm_fetch(extract_dbm(vdb), key);
- if (answer.dptr) {
- value res = alloc_string(answer.dsize);
- memmove (String_val (res), answer.dptr, answer.dsize);
- return res;
- }
- else raise_not_found();
-}
-
-value caml_dbm_insert(value vdb, value vkey, value vcontent) /* ML */
-{
- 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(extract_dbm(vdb), key, content, DBM_INSERT)) {
- case 0:
- return Val_unit;
- case 1: /* DBM_INSERT and already existing */
- raise_dbm("Entry already exists");
- default:
- raise_dbm("dbm_store failed");
- }
-}
-
-value caml_dbm_replace(value vdb, value vkey, value vcontent) /* ML */
-{
- 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(extract_dbm(vdb), key, content, DBM_REPLACE)) {
- case 0:
- return Val_unit;
- default:
- raise_dbm("dbm_store failed");
- }
-}
-
-value caml_dbm_delete(value vdb, value vkey) /* ML */
-{
- datum key;
- key.dptr = String_val(vkey);
- key.dsize = string_length(vkey);
-
- if (dbm_delete(extract_dbm(vdb), key) < 0)
- raise_dbm("dbm_delete");
- else return Val_unit;
-}
-
-value caml_dbm_firstkey(value vdb) /* ML */
-{
- datum key = dbm_firstkey(extract_dbm(vdb));
-
- if (key.dptr) {
- value res = alloc_string(key.dsize);
- memmove (String_val (res), key.dptr, key.dsize);
- return res;
- }
- else raise_not_found();
-}
-
-value caml_dbm_nextkey(value vdb) /* ML */
-{
- datum key = dbm_nextkey(extract_dbm(vdb));
-
- if (key.dptr) {
- value res = alloc_string(key.dsize);
- memmove (String_val (res), key.dptr, key.dsize);
- return res;
- }
- else raise_not_found();
-}
diff --git a/otherlibs/dbm/dbm.ml b/otherlibs/dbm/dbm.ml
deleted file mode 100644
index 26fbb80a5..000000000
--- a/otherlibs/dbm/dbm.ml
+++ /dev/null
@@ -1,58 +0,0 @@
-(***********************************************************************)
-(* *)
-(* OCaml *)
-(* *)
-(* Francois Rouaix, projet Cristal, INRIA Rocquencourt *)
-(* *)
-(* Copyright 1996 Institut National de Recherche en Informatique et *)
-(* en Automatique. All rights reserved. This file is distributed *)
-(* under the terms of the GNU Library General Public License, with *)
-(* the special exception on linking described in file ../../LICENSE. *)
-(* *)
-(***********************************************************************)
-
-(* $Id$ *)
-
-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 raw_opendbm : string -> open_flag list -> int -> t
- = "caml_dbm_open"
-
-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
- file (we must register the exception). Since t is abstract, programs
- have to call it in order to do anything *)
-
-external close : t -> unit = "caml_dbm_close"
-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 _ = Callback.register_exception "dbmerror" (Dbm_error "")
-
-(* Usual iterator *)
-let iter f t =
- let rec walk = function
- None -> ()
- | Some k ->
- f k (find t k);
- walk (try Some(nextkey t) with Not_found -> None)
- in
- walk (try Some(firstkey t) with Not_found -> None)
diff --git a/otherlibs/dbm/dbm.mli b/otherlibs/dbm/dbm.mli
deleted file mode 100644
index 9a0c49212..000000000
--- a/otherlibs/dbm/dbm.mli
+++ /dev/null
@@ -1,79 +0,0 @@
-(***********************************************************************)
-(* *)
-(* OCaml *)
-(* *)
-(* Francois Rouaix, projet Cristal, INRIA Rocquencourt *)
-(* *)
-(* Copyright 1996 Institut National de Recherche en Informatique et *)
-(* en Automatique. All rights reserved. This file is distributed *)
-(* under the terms of the GNU Library General Public License, with *)
-(* the special exception on linking described in file ../../LICENSE. *)
-(* *)
-(***********************************************************************)
-
-(* $Id$ *)
-
-(** Interface to the NDBM database. *)
-
-type t
-(** The type of file descriptors opened on NDBM databases. *)
-
-
-type open_flag =
- Dbm_rdonly
- | Dbm_wronly
- | Dbm_rdwr
- | Dbm_create
-(** Flags for opening a database (see {!Dbm.opendbm}). *)
-
-
-exception Dbm_error of string
-(** Raised by the following functions when an error is encountered. *)
-
-val opendbm : string -> open_flag list -> int -> t
-(** Open a descriptor on an NDBM database. The first argument is
- the name of the database (without the [.dir] and [.pag] suffixes).
- The second argument is a list of flags: [Dbm_rdonly] opens
- the database for reading only, [Dbm_wronly] for writing only,
- [Dbm_rdwr] for reading and writing; [Dbm_create] causes the
- database to be created if it does not already exist.
- The third argument is the permissions to give to the database
- files, if the database is created. *)
-
-external close : t -> unit = "caml_dbm_close"
-(** Close the given descriptor. *)
-
-external find : t -> string -> string = "caml_dbm_fetch"
-(** [find db key] returns the data associated with the given
- [key] in the database opened for the descriptor [db].
- Raise [Not_found] if the [key] has no associated data. *)
-
-external add : t -> string -> string -> unit = "caml_dbm_insert"
-(** [add db key data] inserts the pair ([key], [data]) in
- the database [db]. If the database already contains data
- associated with [key], raise [Dbm_error "Entry already exists"]. *)
-
-external replace : t -> string -> string -> unit = "caml_dbm_replace"
-(** [replace db key data] inserts the pair ([key], [data]) in
- the database [db]. If the database already contains data
- associated with [key], that data is discarded and silently
- replaced by the new [data]. *)
-
-external remove : t -> string -> unit = "caml_dbm_delete"
-(** [remove db key data] removes the data associated with [key]
- in [db]. If [key] has no associated data, raise
- [Dbm_error "dbm_delete"]. *)
-
-external firstkey : t -> string = "caml_dbm_firstkey"
-(** See {!Dbm.nextkey}.*)
-
-external nextkey : t -> string = "caml_dbm_nextkey"
-(** Enumerate all keys in the given database, in an unspecified order.
- [firstkey db] returns the first key, and repeated calls
- to [nextkey db] return the remaining keys. [Not_found] is raised
- when all keys have been enumerated. *)
-
-val iter : (string -> string -> 'a) -> t -> unit
-(** [iter f db] applies [f] to each ([key], [data]) pair in
- the database [db]. [f] receives [key] as first argument
- and [data] as second argument. *)
diff --git a/otherlibs/dbm/libmldbm.clib b/otherlibs/dbm/libmldbm.clib
deleted file mode 100644
index 3a63b870d..000000000
--- a/otherlibs/dbm/libmldbm.clib
+++ /dev/null
@@ -1 +0,0 @@
-cldbm.o