Did you know ... | Search Documentation: |
Pack memo -- prolog/memo.pl |
This module provides the ability to store the results of expensive to run deterministic predicates to save recomputation. The memo table can be volatile (in memory only) and therefore lost when SWI terminates, or stored persistently on disk using the facilities provided by library(persistency).
Suppose you have a predicate expensive/4 which is deterministic with two inputs and two outputs, eg, its PlDoc comment could look like this:
%% expensive(+In1:atom, +In2:int, -Out1:float, -Out2:compound) is det.
Then a volatile memo could be declared with the following directive:
:- volatile_memo expensive( +atom, +int, -float, -compound).
This causes a dynamic predicate expensive/5 to be declared (the extra argument is for metadata about the computation that produced the result). It also causes the definition of the predicate expensive/4 to be renamed to compute_expensive/4, and a new expensive/4 is generated which looks in the memo table (expensive/5) to avoid recomputations.
To declare a persistently memoised predicate, you would use
:- persistent_memo expensive( +atom, +int, -float, -compound).
This causes a persistent predicate expensive/5 to be declared via facilities provided by library(persistency). Otherwise, things look the same externally (there are some internal differences). It is the caller's responsibility to attach a persistent database.
Each volatile_memo/1 or persistent_memo/1 directive can contain one or more predicate declarations, where each argument of the predicate declaration term specifies an input or out argument of the predicate to be memoised. The predicate will be treated as semi-deterministic in the sense that it will succeed at most once for each combination of inputs. Each argument specifier must look like one of these:
Memoised predicates can be accessed at a 'meta-level' using some meta-predicates which you can think of as modal operators.
First of all, each memoised call to the base predicate has some recorded
meta-data whose type is metadata
, defined below:
metadata == pair(comp_event,result). pair(A,B) ---> A-B. result ---> ok ; fail ; ex(any). comp_event ---> comp(hostname,time,duration) ; comp(hostname,duration) ; none. hostname == ground. time == float. duration == float.
Thus, the meta-data can record the computer on which the computation was done, the time it was called (as returned by get_time/1), the duration of the computation in seconds, and whether or not the computation succeeded, failed, or threw an exception. The fact that failures and exception-throwings are recorded means that object level interface (eg expensive/4 in the example above) avoids repeating unsuccessful computation as well as successful ones.
The meta-level browse/1 and browse/2 allow you to access this information.
browse(Goal)
is a nondeterministic predicate which unifies Goal with all the
successful calls in the memo table. browse(Goal,Meta)
matches all calls in the
memo table including unsuccessful ones.
The meta-level clear_all/1 and clear_all/2 allow you to delete memo table entries.
The meta-level memo(Goal)
is the same as the object level Goal, failing or
throwing an expection depending on what the underlying predicate does, but
the meta-level memo(Goal,Meta)
catches failures and exceptions, returning the
meta-data in Meta.
Finally, the meta-level compute/1 by-passes all the memoisation machinery and calls the original underlying predicate directly. This is useful in cases where you absolutely need any side-effects caused by the original computation. compute/2 is the same except that failures and exceptions are reified as meta-data.
The meta-data includes the host name of the computer used to do the
computations. On a Unix system, this should get picked up from the environment
automatically, using getenv('HOSTNAME',Hostname)
(see getenv/2) OR,
if this fails, by calling the shell command 'hostname'.
TODO
:
:- volatile_memo pred1( ArgSpec1, ArgSpec2), pred2(ArgSpec3,ArgSpec4,ArgSpec5).
where ArgSpec1 etc are argument specifiers= as defined in the module header comment. It must look like +Type, -Type, +Name:Type or -Name:Type. Name, if given is not used.
:- persistent_memo pred1( ArgSpec1, ArgSpec2), pred2( ArgSpec3, ArgSpec4, ArgSpec5).
where ArgSpec1 etc are argument specifiers= as defined in the module header comment. It must look like +Type, -Type, +Name:Type or -Name:Type. Name, if given is only used for the declaration of the persistent memo table.
browse(Goal)
is equivalent
to browse(Goal, _-ok)
.
Asks for confirmation if more than N entries are to be deleted, where N is determined
by the setting memo:confirmation_threshold (see library(settings)). The default is 1.
The confirmation message is printed with ansi_format/3 using a style determined by setting
memo:confirmation_style, whose default is [bold,fg(red)
]. The user must type "yes" and
press return continue, otherwise an operation_cancelled
is thrown.
Note that the types are checked strictly. An Input argument X declared with +T
must satisfy must_be(T,X)
. An output argument declared with a -T may be bound or unbound.
If it is bound, the predicate behaves as if it were unbound, followed by a final
semi-deterministic unification. (Prior to v0.5.0, outputs had to be unbound.)
memo_property ---> type(typespec) ; storage(oneof([persistent,volatile])) ; count(natural). .
Enumerates memoised and their properties.
The following predicates are exported, but not or incorrectly documented.