
tabling.pl -- Tabled execution (SLG WAM)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.
table :PredicateIndicators:- 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
start_tabling(:Closure, :Wrapper, :Implementation)
start_subsumptive_tabling(:Closure, :Wrapper, :Implementation)answer(s).
start_abstract_tabling(:Closure, :Wrapper, :Worker)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)
update(+Flags, +Head, +Module, +A1, +A2, -A3, -Action) is semidettrue, A1 should be deleted.
tnot(:Goal)(*): Only variant tabling is allowed under tnot/1.
not_exists(:P) is semidet
$wfs_call(:Goal, :Delays)
abolish_all_tablesAbolishes 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_module_tables(+Module) is det
abolish_nonincremental_tables is det
abolish_nonincremental_tables(+Options)
current_table(:Variant, -Trie) is nondet
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
$set_table_wrappers(:Head)
$start_monotonic(+Head, +Wrapped)
monotonic_update(+Action, +ClauseRef)
abolish_monotonic_tables
dyn_update(+Action, +Context) is det
answer_completion(+AnswerTrie, +Return) is detsimplify_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.
tripwire(+Wire, +Action, +Context)abstract and
bounded_rationality.The following predicates are exported, but not or incorrectly documented.
$tbl_answer(Arg1, Arg2, Arg3, Arg4)
$moded_wrap_tabled(Arg1, Arg2, Arg3, Arg4, Arg5)
abolish_shared_tables
$wrap_tabled(Arg1, Arg2)
abolish_private_tables