This library handled tabled execution of predicates using the
characteristics if the SLG WAM. The required suspension is realised
using delimited continuations implemented by reset/3 and shift/1. The
table space and work lists are part of the SWI-Prolog core.
- author
- - Benoit Desouter, Jan Wielemaker and Fabrizio Riguzzi
table :PredicateIndicators- Prepare the given PredicateIndicators for tabling. This predicate is
normally used as a directive, but SWI-Prolog also allows runtime
conversion of non-tabled predicates to tabled predicates by calling
table/1. The example below prepares the predicate edge/2 and the
non-terminal statement//1 for tabled execution.
:- table edge/2, statement//1.
In addition to using predicate indicators, a predicate can be
declared for mode directed tabling using a term where each
argument declares the intended mode. For example:
:- table connection(_,_,min).
Mode directed tabling is discussed in the general introduction
section about tabling.
untable(M:PIList) is det- Remove tabling for the predicates in PIList. This can be used to
undo the effect of table/1 at runtime. In addition to removing the
tabling instrumentation this also removes possibly associated tables
using abolish_table_subgoals/1.
- Arguments:
-
PIList | - is a comma-list that is compatible ith table/1. |
start_tabling(:Closure, :Wrapper, :Implementation)- Execute Implementation using tabling. This predicate should not be
called directly. The table/1 directive causes a predicate to be
translated into a renamed implementation and a wrapper that involves
this predicate.
- Arguments:
-
Closure | - is the wrapper closure to find the predicate quickly.
It is also allowed to pass nothing. In that cases the predicate is
looked up using Wrapper. We suggest to pass 0 in this case. |
- Compatibility
- - This interface may change or disappear without notice
from future versions.
start_subsumptive_tabling(:Closure, :Wrapper, :Implementation)- (*) We should not use trie_gen_compiled/2 here as this will
enumerate all answers while '$tbl_answer_update_dl'/2 uses the
available trie indexing to only fetch the relevant
answer(s)
.
- To be done
- - In the end '$tbl_answer_update_dl'/2 is problematic with
incremental and shared tabling as we do not get the consistent
update view from the compiled result.
start_abstract_tabling(:Closure, :Wrapper, :Worker)- Deal with
table p/1 as subgoal_abstract(N)
. This is a merge
between variant and subsumptive tabling. If the goal is not
abstracted this is simple variant tabling. If the goal is abstracted
we must solve the more general goal and use answers from the
abstract table.
Wrapper is e.g., user:p(s(s(s(X))),Y)
Worker is e.g., call(<closure>(p/2)(s(s(s(X)))
,Y))
start_moded_tabling(+Closure, :Wrapper, :Implementation, +Variant, +ModeArgs)- As start_tabling/2, but in addition separates the data stored in the
answer trie in the Variant and ModeArgs.
update(+Flags, +Head, +Module, +A1, +A2, -A3, -Action) is semidet- Update the aggregated value for an answer. Iff this predicate
succeeds, the aggregated value is updated to A3. If Del is unified
with
true
, A1 should be deleted.
- Arguments:
-
Flags | - is a bit mask telling which of A1 and A2 are unconditional |
Head | - is the head of the predicate |
Module | - is the module of the predicate |
A1 | - is the currently aggregated value |
A2 | - is the newly produced value |
Action | - is one of
delete to replace the old answer with the new
keep to keep the old answer and add the new
done to stop the update process
|
tnot(:Goal)- Tabled negation.
(*): Only variant tabling is allowed under tnot/1.
not_exists(:P) is semidet- Tabled negation for non-ground goals. This predicate uses the tabled
meta-predicate tabled_call/1. The tables for tabled_call/1 must
be cleared if `the world changes' as well as to avoid aggregating
too many variants.
$wfs_call(:Goal, :Delays)- Call Goal and provide WFS delayed goals as a conjunction in Delays.
This predicate is the internal version of call_delays/2 from
library(wfs).
abolish_all_tables- Remove all tables. This is normally used to free up the space or
recompute the result after predicates on which the result for some
tabled predicates depend.
Abolishes both local and shared tables. Possibly incomplete tables
are marked for destruction upon completion. The dependency graphs
for incremental and monotonic tabling are reclaimed as well.
abolish_table_subgoals(:Subgoal) is det- Abolish all tables that unify with SubGoal.
- To be done
- - : SubGoal must be callable. Should we allow for more general
patterns?
abolish_module_tables(+Module) is det- Abolish all tables for predicates associated with the given module.
abolish_nonincremental_tables is det- Abolish all tables that are not related to incremental predicates.
abolish_nonincremental_tables(+Options)- Allow for skipping incomplete tables while abolishing.
- To be done
- - Mark tables for destruction such that they are abolished when
completed.
current_table(:Variant, -Trie) is nondet- True when Trie is the answer table for Variant. If Variant has an
unbound module or goal, all possible answer tries are generated,
otherwise Variant is considered a fully instantiated variant and the
predicate is semidet.
first(+S0, +S1, -S) is det
last(+S0, +S1, -S) is det
min(+S0, +S1, -S) is det
max(+S0, +S1, -S) is det
sum(+S0, +S1, -S) is det- Implement YAP tabling modes.
$set_table_wrappers(:Head)- Clear/add wrappers and notifications to trap dynamic predicates.
This is required both for incremental and monotonic tabling.
$start_monotonic(+Head, +Wrapped)- This is called the monotonic wrapper around a dynamic predicate to
collect the dependencies between the dynamic predicate and the
monotonic tabled predicates.
monotonic_update(+Action, +ClauseRef)- Trap changes to the monotonic dynamic predicate and forward them.
abolish_monotonic_tables- Abolish all monotonic tables and the monotonic dependency relations.
- To be done
- - : just prepare for incremental reevaluation?
dyn_update(+Action, +Context) is det- Track changes to added or removed clauses. We use '$clause'/4
because it works on erased clauses.
- To be done
- - Add a '$clause_head'(-Head, +ClauseRef) to only decompile the
head.
answer_completion(+AnswerTrie, +Return) is det- Find positive loops in the residual program and remove the
corresponding answers, possibly causing additional simplification.
This is called from C if
simplify_component()
detects there are
conditional answers after simplification.
Note that we are called recursively from C. Our caller prepared a
clean new tabling environment and restores the old one after this
predicate terminates.
- author
- - This code is by David Warren as part of XSB.
- See also
- - called from C, pl-tabling.c,
answer_completion()
tripwire(+Wire, +Action, +Context)- Called from the tabling engine of some tripwire is exceeded and the
situation is not handled internally (such as
abstract
and
bounded_rationality
.
- undefined is undefined
- Expresses the value bottom from the well founded semantics.
- answer_count_restraint is undefined
- radial_restraint is undefined
- Similar to undefined/0, providing a specific undefined for
restraint violations.
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.
$wrap_tabled(Arg1, Arg2)
$tbl_answer(Arg1, Arg2, Arg3, Arg4)
$moded_wrap_tabled(Arg1, Arg2, Arg3, Arg4, Arg5)
- radial_restraint
abolish_shared_tables
abolish_private_tables