1:- module(bdb_wrapper,
    2    [
    3        bdb_base/1,
    4        bdb_erase/1,
    5        bdb_erase/2,
    6        bdb_retrieve/3,
    7        bdb_store/3
    8    ]).

Persistence using Berkeley DB

This module provides a simple, minimalistic approach to implementing persistence on the SWI-Prolog platform, by means of the Berkeley DB utility package. The target data is organized in DataSets. A DataSet is comprised of one or more TagSets, and a TagSet is a named collection of Prolog data.

Berkeley DB is an open-source software library intended to provide a high-performance embedded database for key/value data. The database storage is organized as a directory tree, starting with a root path specified with bdb_path/1.

Being an embedded database implies that the library provides access to files containing one or more database tables. These tables are always binary, mapping keys to values. The SWI-Prolog interface to Berkeley DB allows for fast storage of arbitrary Prolog terms, including cycles and constraints.

On Windows, the package Berkeley DB for Windows version 6.2.38 must have been installed. The installers db-6.2.28_86.msi (32 bits) and db-6.2.28_64.msi (64 bits) may be obtained directly at the Oracle Berkeley DB site.

Most Linux distributions already carry the Berkeley DB library by default. Additionally, on Linux environments SWI-Prolog requires that the package swi-prolog-bdb be installed.

The Linux db-util package is fully compatible with the database structure created by SWI-Prolog through Berkeley DB. For the db-util manpages, please refer to https://manpages.debian.org/jessie/db-util/index.html .

Please, refer to https://www.swi-prolog.org/pldoc/doc/_SWI_/library/bdb.pl for additional instructions on how to use Berkeley DB.

author
- GT Nunes
version
- 1.3.2
license
- BSD-3-Clause License */
   48%-------------------------------------------------------------------------------------
   49
   50:- use_module(library(codesio),
   51    [
   52        format_to_codes/3
   53    ]).   54
   55:- use_module(library(filesex),
   56    [
   57        delete_directory_and_contents/1
   58    ]).   59
   60:- dynamic  swi_bdb_base/1.   61:- volatile swi_bdb_base/1.   62
   63%-------------------------------------------------------------------------------------
 bdb_base(+BasePath:atom) is det
bdb_base(-BasePath:atom) is semidet
Unify BasePath with the base path for Berkeley DB's persistence files.

BasePath Atom identifying the base path for Berkeley DB's persistence files

   72bdb_base(BasePath) :-
   73
   74    (var(BasePath) ->
   75        swi_bdb_base(BasePath)
   76    ;
   77        % register the base path for Berkeley DB (make sure it is '/'-terminated)
   78        (retract(swi_bdb_base(_)) ; true),
   79        !,
   80        (sub_atom(BasePath, _, 1, 0, '/') ->
   81            BdbPath = BasePath
   82        ;
   83            atom_concat(BasePath, '/', BdbPath)
   84        ),
   85        assertz(swi_bdb_base(BdbPath))
   86    ),
   87
   88    % make sure path exists
   89    (exists_directory(BasePath) ->
   90       true
   91    ;
   92       make_directory(BasePath)
   93    ).
 bdb_store(+TagSet:atom, +DataSet:atom, +Data:data) is det
Persist Data to external storage.
Arguments:
TagSet- Atom identifying the tagset to store
DataSet- Atom identifying the dataset storage location fragment
Data- The data to store
  103bdb_store(TagSet, DataSet, Data) :-
  104
  105    % obtain the storage filepath for this dataset 
  106    storage_path(TagSet, DataSet, DsPath),
  107
  108    % create base directory, if necessary
  109    file_directory_name(DsPath, BaseDir),
  110    (exists_directory(BaseDir) ->
  111        true
  112    ;
  113        make_directory(BaseDir)
  114    ),
  115
  116    !,
  117    % fail point (create the database)
  118    catch(bdb_open(DsPath, update, DbRef, []), _, fail),
  119
  120    !,
  121    % fail point (store the data)
  122    catch(bdb_put(DbRef, data, Data), _, fail),
  123
  124    !,
  125    % fail point (close the database)
  126    catch(bdb_close(DbRef), _, fail).
 bdb_retrieve(+TagSet:atom, +DataSet:atom, -Data:data) is det
Retrieve Data from external storage.
Arguments:
TagSet- Atom identifying the tagset to store
DataSet- Atom identifying the dataset storage location fragment
Data- The data to retrieve
  136bdb_retrieve(TagSet, DataSet, Data) :-
  137
  138    % obtain the storage filepath for this dataset 
  139    storage_path(TagSet, DataSet, DsPath),
  140
  141    !,
  142    % fail point (open the database)
  143    catch(bdb_open(DsPath, read, DbRef, []), _, fail),
  144
  145    !,
  146    % fail point (retrieve the data)
  147    catch(bdb_get(DbRef, data, Data), _, fail),
  148
  149    !,
  150    % fail point (close the database)
  151    catch(bdb_close(DbRef), _, fail).
 bdb_erase(+DataSet:atom) is det
Remove all the data associated with DataSet from external storage.
Arguments:
DataSet- Atom identifying the dataset storage location fragment
  159bdb_erase(DataSet) :-
  160
  161    % obtain the base storage location
  162    storage_path('*', DataSet, DsPath),
  163    file_directory_name(DsPath, BaseDir),
  164
  165    % delete storage directory, if necessary
  166    (exists_directory(BaseDir) ->
  167        delete_directory_and_contents(BaseDir)
  168    ;
  169        true
  170    ).
 bdb_erase(+TagSet:atom, +DataSet:atom) is det
Erase the data associated with the TagSet within DataSet from external storage.
Arguments:
TagSet- Atom identifying the dataset to erase
DataSet- Atom identifying the dataset storage location fragment
  178bdb_erase(TagSet, DataSet) :-
  179
  180    % obtain the storage filepath for this dataset 
  181    storage_path(TagSet, DataSet, DsPath),
  182
  183    % delete it, if necessary
  184    (\+ exists_file(DsPath) ; (delete_file(DsPath))).
  185
  186%-------------------------------------------------------------------------------------
 storage_path(+TagSet:atom, +DataSet:atom, -DsPath:atom) is det
Unify DsPath with the directory pointing to the DataSet / TagSet repository.
Arguments:
TagSet- Atom identifying the dataset
DataSet- Atom identifying the dataset storage location fragment
DsPath- The BDB storage path
  196storage_path(TagSet, DataSet, DsPath) :-
  197
  198    % obtain the registered base path
  199    (swi_bdb_base(BasePath) ; BasePath = ''),
  200    !,
  201
  202    % build the base directory
  203    atom_concat(BasePath, DataSet, BaseDir),
  204
  205    % build the storage path
  206    format_to_codes('~a/~a.dbd', [BaseDir,TagSet], Codes),
  207    atom_codes(DsPath, Codes)