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. |
set_pattributes(:Head, +Options) is det[private]- Set all tabling attributes for Head. These have been collected using
table_options/3 from the
:- table Head as (Attr1,...)
directive.
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.
restart_tabling(+Closure, +Wrapper, +Worker)[private]- We were aborted due to a deadlock. Simply retry. We sleep a very
tiny amount to give the thread against which we have deadlocked the
opportunity to grab our table. Without, it is common that we re-grab
the table within our time slice and before the kernel managed to
wakeup the other thread.
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.
wrapper_skeleton(+GenWrapper, +GenSkeleton, +Wrapper, -Skeleton)[private]- Skeleton is a specialized version of GenSkeleton for the subsumed
new consumer.
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))
done_leader(+Status, +Fresh, +Skeleton, -Clause)[private]- Called on completion of a table. Possibly destroys the component and
generates the answers from the complete table. The last cases deals
with leaders that are merged into a higher SCC (and thus no longer a
leader).
run_leader(+Skeleton, +Worker, +Fresh, -Status, -Clause) is det[private]- Run the leader of a (new) SCC, storing instantiated copies of
Wrapper into Trie. Status is the status of the SCC when this
predicate terminates. It is one of
complete
, in which case local
completion finished or merged
if running the completion finds an
open (not completed) active goal that resides in a parent component.
In this case, this SCC has been merged with this parent.
If the SCC is merged, the answers it already gathered are added to
the worklist and we shift (suspend), turning our leader into an
internal node for the upper SCC.
delim(+Skeleton, +Worker, +WorkList, +Delays)[private]- Call WorkList and add all instances of Skeleton as answer to
WorkList, conditional according to Delays.
- Arguments:
-
Skeleton | - is the return skeleton (ret/N term) |
Worker | - is either the (wrapped) tabled goal or a continuation |
WorkList | - is the work list associated with Worker (or its
continuation). |
Delays | - is the current delay list. Note that the actual delay
also include the internal global delay list.
'$tbl_wkl_add_answer'/4 joins the two. For a dependency we
join the two explicitly. |
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
|
completion(+Component, -Status, -Clause) is det[private]- Wakeup suspended goals until no new answers are generated. Status is
one of
merged
, completed
or final
. If Status is not merged
,
Clause is a compiled representation for the answer trie of the
Component leader.
- $tbl_wkl_work(+WorkList, -Answer, -Continuation, -Wrapper, -TargetWorklist, -Delays) is nondet[private]
- True when Continuation needs to run with Answer and possible answers
need to be added to TargetWorklist. The remaining arguments are
there to restore variable bindings and restore the delay list.
The suspension added by '$tbl_wkl_add_suspension'/2 is a term
dependency(SrcWrapper, Continuation, Wrapper, WorkList, Delays)
.
Note that:
- Answer and Goal must be unified to rebind the input arguments
for the continuation.
- Wrapper is stored in TargetWorklist on successful completion
of the Continuation.
- If Answer Subsumption is in effect, the story is a bit more
complex and ModeArgs provide the binding over which we do
aggregation. Otherwise, ModeArgs is the the
reserved trie node produced by '$tbl_trienode'/1.
- Arguments:
-
Answer | - is the answer term from the answer cluster (node in
the answer trie). For answer subsumption it is a term Ret/ModeArgs |
Goal | - to Delays are extracted from the dependency/5 term in
the same order. |
tnot(:Goal)- Tabled negation.
(*): Only variant tabling is allowed under tnot/1.
negation_suspend(+Goal, +Skeleton, +Worklist)[private]- Suspend Worklist due to negation. This marks the worklist as dealing
with a negative literal and suspend.
The completion step will resume negative worklists that have no
solutions, causing this to succeed.
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.
table_options(+Options, +OptDictIn, -OptDictOut)[private]- Handler the ... as options ... construct.
mode_check(+Moded, -TestCode)[private]- Enforce the output arguments of a mode-directed tabled predicate to
be unbound.
extract_modes(+ModeSpec, +Head, -Variant, -Modes, -ModedAnswer) is det[private]- Split Head into its variant and term that matches the moded
arguments.
- Arguments:
-
ModedAnswer | - is a term that captures that value of all moded
arguments of an answer. If there is only one, this is the value
itself. If there are multiple, this is a term s(A1,A2,...) |
separate_args(+ModeSpecArgs, +HeadArgs, -NoModesArgs, -Modes, -ModeArgs) is det[private]- Split the arguments in those that need to be part of the variant
identity (NoModesArgs) and those that are aggregated (ModeArgs).
- Arguments:
-
Args | - seems a copy of ModeArgs, why? |
updater_clauses(+Modes, +Head, -Clauses)[private]- Generates a clause to update the aggregated state. Modes is
a list of predicate names we apply to the state.
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.
mon_assert_dep(+Dependency, +Continuation, +Skel, +ATrie) is det[private]- Create a dependency for monotonic tabling. Skel and ATrie are the
target trie for solutions of Continuation.
monotonic_affects(+SrcTrie, +SrcReturn, -IsMono, -Continuation, -Return, -Atrie)[private]- Dependency between two monotonic tables. If SrcReturn is added to
SrcTrie we must add all answers for Return of Continuation to Atrie.
IsMono shares with Continuation and is used in start_tabling/3 to
distinguish normal tabled call from propagation.
monotonic_dyn_affects(:Head, -Continuation, -Return, -ATrie)[private]- Dynamic predicate that maintains the dependency from a monotonic
wrap_monotonic(:Head)[private]- Prepare the dynamic predicate Head for monotonic tabling. This traps
calls to build the dependency graph and updates to propagate answers
from new clauses through the dependency graph.
unwrap_monotonic(+Head)[private]- Remove the monotonic wrappers and dependencies.
$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.
mon_propagate(+Action, +Head, +ClauseRef)[private]- Handle changes to a dynamic predicate as part of monotonic
updates.
propagate_assert(+Head) is det[private]- Propagate assertion of a dynamic clause with head Head.
incr_propagate_assert(+Head) is det[private]- Propagate assertion of a dynamic clause with head Head, both
through eager and dynamic tables.
propagate_answer(+SrcTrie, +SrcSkel) is det[private]- Propagate the new answer SrcSkel to the answer table SrcTrie.
pdelim(+Worker, +Skel, +ATrie)[private]- Call Worker (a continuation) and add each binding it provides for
Skel to ATrie. If a new answer is added to ATrie, using
propagate_answer/2 to propagate this further. Note that we may hit
new dependencies and thus we need to run this using reset/3.
- To be done
- - Not sure whether we need full tabling here. Need to think of
test cases.
mon_invalidate_dependents(+Head)[private]- A non-monotonic operation was done on Head. Invalidate all dependent
tables, preparing for normal incremental reevaluation on the next
cycle.
abolish_monotonic_tables- Abolish all monotonic tables and the monotonic dependency relations.
- To be done
- - : just prepare for incremental reevaluation?
wrap_incremental(:Head) is det[private]- Wrap an incremental dynamic predicate to be added to the IDG.
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.
unwrap_incremental(:Head) is det[private]- Remove dynamic predicate incremenal forwarding, reset the possible
abstract
property and remove possible tables.
reeval(+ATrie, :Goal, ?Return) is nondet[private]- Called if the table ATrie is out-of-date (has non-zero
falsecount). The answers of this predicate are the answers to Goal
after re-evaluating the answer trie.
This finds all dependency paths to dynamic predicates and then
evaluates the nodes in a breath-first fashion starting at the level
just above the dynamic predicates and moving upwards. Bottom up
evaluation is used to profit from upward propagation of not-modified
events that may cause the evaluation to stop early.
Note that false paths either end in a dynamic node or a complete
node. The latter happens if we have and IDG "D -> P -> Q" and we
first re-evaluate P for some reason. Now Q can still be invalid
after P has been re-evaluated.
- Arguments:
-
ATrie | - is the answer trie. When shared tabling, we own this
trie. |
Goal | - is tabled goal (variant). If we run into a deadlock we
need to call this. |
Return | - is the return skeleton. We must run
trie_gen_compiled(ATrie, Return) to enumerate the answers |
clean_paths(+PathsIn, -Paths)[private]- Clean the reevaluation paths. Get rid of the head term for ranking
and remove duplicate paths. Note that a Path is a list of tries,
ground terms.
reeval_paths(+Paths, +Atrie)[private]- Make Atrie valid again by re-evaluating nodes in Paths. We stop as
soon as Atrie is valid again. Note that we may not need to
reevaluate all paths because evaluating the head of some path may
include other nodes in an SCC, making them valid as well.
false_path(+Atrie, -Path) is nondet[private]- True when Path is a list of invalid tries (bottom up, ending with
ATrie). The last element of the list is a term
s(Rank,Length,ATrie)
that is used for sorting the paths.
If we find a table along the way that is being worked on by some
other thread we wait for it.
reeval_node(+ATrie) is semidet[private]- Re-evaluate the invalid answer trie ATrie. Initially this created a
nested tabling environment, but this is dropped:
- It is possible for the re-evaluating variant to call into outer
non/not-yet incremental tables, requiring a merge with this
outer SCC. This doesn't work well with a sub-environment.
- We do not need one. If this environment is not merged into the
outer one it will complete before we continue.
Fails if the node is not ready for evaluation. This is the case if
it is valid or it is a lazy table that has invalid dependencies.
reeval_nodes(+Nodes:list(trie)) is det[private]- After pulling in the monotonic answers into some node, this is a
list if invalid dependencies. We must revaluate these and then pull
in possible queued answers before we are done.
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()
delete_answers_for_failing_calls(-Propagated)[private]- Delete answers whose condition is determined to be
false
and
return the number of additional answers that changed status as a
consequence of additional simplification propagation.
eval_dl_in_residual(+Condition)[private]- Evaluate a condition by only looking at the residual goals of the
involved calls.
eval_subgoal_in_residual(+AnswerTrie, ?Return)[private]- Derive answers for the variant represented by AnswerTrie based on
the residual goals only.
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.
$tbl_answer(Arg1, Arg2, Arg3, Arg4)
$wrap_tabled(Arg1, Arg2)
$moded_wrap_tabled(Arg1, Arg2, Arg3, Arg4, Arg5)
abolish_private_tables
abolish_shared_tables
- radial_restraint