
persistency.pl -- Provide persistent dynamic predicatesThis module provides simple persistent storage for one or more dynamic predicates. A database is always associated with a module. A module that wishes to maintain a database must declare the terms that can be placed in the database using the directive persistent/1.
The persistent/1 expands each declaration into four predicates:
name(Arg, ...)assert_name(Arg, ...)retract_name(Arg, ...)retractall_name(Arg, ...)As mentioned, a database can only be accessed from within a single module. This limitation is on purpose, forcing the user to provide a proper API for accessing the shared persistent data.
Below is a simple example:
:- module(user_db,
[ attach_user_db/1, % +File
current_user_role/2, % ?User, ?Role
add_user/2, % +User, +Role
set_user_role/2 % +User, +Role
]).
:- use_module(library(persistency)).
:- persistent
user_role(name:atom, role:oneof([user,administrator])).
attach_user_db(File) :-
db_attach(File, []).
%% current_user_role(+Name, -Role) is semidet.
current_user_role(Name, Role) :-
with_mutex(user_db, user_role(Name, Role)).
add_user(Name, Role) :-
assert_user_role(Name, Role).
set_user_role(Name, Role) :-
user_role(Name, Role), !.
set_user_role(Name, Role) :-
with_mutex(user_db,
( retractall_user_role(Name, _),
assert_user_role(Name, Role))).
persistent(+Spec)
:- persistent
<callable>,
<callable>,
...
Each specification is a callable term, following the conventions of library(record), where each argument is of the form
name:type
Types are defined by library(error).
current_persistent_predicate(:PI) is nondet
db_attach(:File, +Options)close (close journal after write), flush
(default, flush journal after write) or none
(handle as fully buffered stream).
If File is already attached this operation may change the sync
behaviour.
db_size(+Module, -Terms) is det[private]
db_attached(:File) is semidet
db_assert(:Term) is det[private]
db_detach is det
sync(+Module, +Stream) is det[private]close, the journal
file is closed, making it easier to edit the file externally.
Using flush flushes the stream but does not close it. This
provides better performance. Using none, the stream is not
even flushed. This makes the journal sensitive to crashes, but
much faster.
db_retractall(:Term) is det[private]
db_retract(:Term) is nondet[private]
db_sync(:What)reload, but use incremental loading if possible.
This allows for two processes to examine the same database
file, where one writes the database and the other periodycally
calls db_sync(update) to follow the modified data.gc(50).With unbound What, db_sync/1 reloads the database if it was modified on disk, gc it if it is dirty and close it if it is opened.
db_sync_all(+What)