% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \section{library(persistency): Provide persistent dynamic predicates} \label{sec:persistency} \begin{tags} \mtag{To be done}- Provide type safety while loading \\- Thread safety must now be provided at the user-level. Can we provide generic thread safety? Basically, this means that we must wrap all exported predicates. That might better be done outside this library. \\- Transaction management? \\- Should assert_$<$name$>$ only assert if the database does not contain a variant? \\- Since we have \predref{prolog_listen}{2}, we could use direct \predref{assert}{1} and \predref{retract}{1} and use the system hooks to deal with the updates. \end{tags} This 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 \predref{persistent}{1}. The \predref{persistent}{1} expands each declaration into four predicates: \begin{shortlist} \item \verb$name(Arg, ...)$ \item \verb$assert_name(Arg, ...)$ \item \verb$retract_name(Arg, ...)$ \item \verb$retractall_name(Arg, ...)$ \end{shortlist} 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. This module requires the same thread-synchronization as the normal Prolog database. This implies that if each individual assert or retract takes the database from one consistent state to the next, no additional locking is required. If more than one elementary database operation is required to get from one consistent state to the next, both updating and querying the database must be locked using \predref{with_mutex}{2}. Below is a simple example, where adding a user does not need locking as it is a single \textit{assert}, while modifying a user requires both a retract and assert and thus needs to be locked. \begin{code} :- 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))). \end{code} \vspace{0.7cm} \begin{description} \prefixop{persistent}{+Spec} Declare dynamic database terms. Declarations appear in a directive and have the following format: \begin{code} :- persistent , , ... \end{code} Each specification is a callable term, following the conventions of \file{library(record)}, where each argument is of the form \begin{code} name:type \end{code} Types are defined by \file{library(error)}. \predicate[nondet]{current_persistent_predicate}{1}{:PI} True if \arg{PI} is a predicate that provides access to the persistent database DB. \predicate{db_attach}{2}{:File, +Options} Use \arg{File} as persistent database for the calling module. The calling module must defined \predref{persistent}{1} to declare the database terms. Defined options: \begin{description} \termitem{sync}{+Sync} One of \const{close} (close journal after write), \const{flush} (default, flush journal after write) or \const{none} (handle as fully buffered stream). \end{description} If \arg{File} is already attached this operation may change the \const{sync} behaviour. \predicate[semidet]{db_attached}{1}{:File} True if the context module attached to the persistent database \arg{File}. \predicate[det]{db_assert}{1}{:Term} Assert \arg{Term} into the database and record it for persistency. Note that if the on-disk file has been modified it is first reloaded. \predicate[det]{db_detach}{0}{} Detach persistency from the calling module and delete all persistent clauses from the Prolog database. Note that the file is not affected. After this operation another file may be attached, providing it satisfies the same persistency declaration. \predicate[det]{db_retractall}{1}{:Term} Retract all matching facts and do the same in the database. If \arg{Term} is unbound, \predref{persistent}{1} from the calling module is used as generator. \predicate[nondet]{db_retract}{1}{:Term} Retract terms from the database one-by-one. \predicate{db_sync}{1}{:What} Synchronise database with the associated file. \arg{What} is one of: \begin{description} \termitem{reload}{} Database is reloaded from file if the file was modified since loaded. \termitem{update}{} As \const{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 \verb$db_sync(update)$ to follow the modified data. \termitem{gc}{} Database was re-written, deleting all retractall statements. This is the same as \verb$gc(50)$. \termitem{gc}{Percentage} GC DB if the number of deleted terms is greater than the given percentage of the total number of terms. \termitem{gc}{always} GC DB without checking the percentage. \termitem{close}{} Database stream was closed \termitem{detach}{} Remove all registered persistency for the calling module \termitem{nop}{} No-operation performed \end{description} With unbound \arg{What}, \predref{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. \predicate{db_sync_all}{1}{+What} Sync all registered databases. \end{description}