• Places
    • Home
    • Graphs
    • Prefixes
  • Admin
    • Users
    • Settings
    • Plugins
    • Statistics
  • Repository
    • Load local file
    • Load from HTTP
    • Load from library
    • Remove triples
    • Clear repository
  • Query
    • YASGUI SPARQL Editor
    • Simple Form
    • SWISH Prolog shell
  • Help
    • Documentation
    • Tutorial
    • Roadmap
    • HTTP Services
  • Login

A The SWI-Prolog library
AllApplicationManualNameSummaryHelp

  • Documentation
    • Reference manual
      • The SWI-Prolog library
        • library(aggregate): Aggregation operators on backtrackable predicates
        • library(apply): Apply predicates on a list
        • library(assoc): Association lists
        • library(broadcast): Broadcast and receive event notifications
        • library(charsio): I/O on Lists of Character Codes
        • library(check): Consistency checking
        • library(clpb): CLP(B): Constraint Logic Programming over Boolean Variables
        • library(clpfd): CLP(FD): Constraint Logic Programming over Finite Domains
        • library(clpqr): Constraint Logic Programming over Rationals and Reals
        • library(csv): Process CSV (Comma-Separated Values) data
        • library(debug): Print debug messages and test assertions
        • library(error): Error generating support
        • library(gensym): Generate unique identifiers
        • library(iostream): Utilities to deal with streams
        • library(lists): List Manipulation
        • library(main): Provide entry point for scripts
        • library(nb_set): Non-backtrackable set
        • library(www_browser): Activating your Web-browser
        • library(option): Option list processing
        • library(optparse): command line parsing
        • library(ordsets): Ordered set manipulation
        • library(pairs): Operations on key-value lists
        • library(persistency): Provide persistent dynamic predicates
        • library(pio): Pure I/O
        • library(predicate_options): Declare option-processing of predicates
        • library(prolog_pack): A package manager for Prolog
        • library(prolog_xref): Cross-reference data collection library
        • library(quasi_quotations): Define Quasi Quotation syntax
        • library(random): Random numbers
        • library(readutil): Reading lines, streams and files
        • library(record): Access named fields in a term
        • library(registry): Manipulating the Windows registry
        • library(simplex): Solve linear programming problems
        • library(solution_sequences): Modify solution sequences
        • library(tabling): Tabled execution (SLG)
          • Example 1: using tabling for memoizing
          • Example 2: avoiding non-termination
          • Mode directed tabling
          • Tabling predicate reference
        • library(thread_pool): Resource bounded thread management
        • library(ugraphs): Unweighted Graphs
        • library(url): Analysing and constructing URL
        • library(varnumbers): Utilities for numbered terms
        • library(yall): Lambda expressions
    • Packages

A.35 library(tabling): Tabled execution (SLG)

The library library(tabling) provides support for Tabled execution of one or more Prolog predicates, also called SLG resolution. Tabling a predicate provides two properties:

  1. Re-evaluation of a tabled predicate is avoided by memoizing the answers. This can realise huge performance enhancements as illustrated in section A.35.1. It also comes with two downsides: the memoized answers are not automatically updated or invalidated if the world (set of predicates on which the answers depend) changes and the answer tables must be stored (in memory).

  2. Left recursion, a goal calling a variant of itself recursively and thus looping under the normal Prolog SLD resolution is avoided by suspending the variant call and resuming it with answers from the table. This is illustrated in section A.35.2.

Tabling is particularly suited to simplify inference over a highly entangled set of predicates that express axioms and rules in a static (not changing) world. When using SLD resolution for such problems, it is hard to ensure termination and avoid frequent recomputation of intermediate results. A solution is to use Datalog style bottom-up evaluation, i.e., applying rules on the axioms and derived facts until a fixed point is reached. However, bottom-up evaluation typically derives many facts that are never used. Tabling provides a goal oriented resolution strategy for such problems and is enabled simply by adding a table/1 directive to the program.

A.35.1 Example 1: using tabling for memoizing

As a first classical example we use tabling for memoizing intermediate results. We use Fibonacci numbers to illustrate the approach. The Fibonacci number I is defined as the sum of the Fibonacci numbers for I-1 and I-2, while the Fibonacci number of 0 and 1 are both defined to be 1. This can be translated naturally into Prolog:

fib(0, 1) :- !.
fib(1, 1) :- !.
fib(N, F) :-
        N > 1,
        N1 is N-1,
        N2 is N-2,
        fib(N1, F1),
        fib(N2, F2),
        F is F1+F2.

The complexity of executing this using SLD resolution however is 2^N and thus becomes prohibitively slow rather quickly, e.g., the execution time for N=30 is already 0.4 seconds. Using tabling, fib(N,F) for each value of N is computed only once and the algorithm becomes linear. Tabling effectively inverts the execution order for this case: it suspends the final addition (F is F1+F2) until the two preceeding Fibonacci numbers have been added to the answer tables. Thus, we can reduce the complexity from the show-stopping 2^N to linear by adding a tabling directive and otherwise not changing the algorithm. The code becomes:

:- use_module(library(tabling)).
:- table fib/2.

fib(0, 1) :- !.
fib(1, 1) :- !.
fib(N, F) :-
        N > 1,
        N1 is N-1,
        N2 is N-2,
        fib(N1, F1),
        fib(N2, F2),
        F is F1+F2.

The price that we pay is that a table fib(I,F) is created for each I in 0..N. The execution time for N=30 is now 1 millisecond and computing the Fibonacci number for N=1000 is doable (output edited for readability).

1 ?- time(fib(1000, X)).
% 52,991 inferences, 0.013 CPU in 0.013 seconds
X = 70330367711422815821835254877183549770181269836358
    73274260490508715453711819693357974224949456261173
    34877504492417659910881863632654502236471060120533
    74121273867339111198139373125598767690091902245245
    323403501.

In the case of Fibonacci numbers we can still rather easily achieve linear complexity using program transformation, where we use bottom-up instead of top-down evaluation, i.e., we compute fib(N,F) for growing N, where we pass the last two Fibonacci numbers to the next iteration. Not having to create the tables and not having to suspend and resume goals makes this implementation about 25 times faster than the tabled one. However, even in this simple case the transformation is not obvious and it is far more difficult to recognise the algorithm as an implementation of Fibonacci numbers.

fib(0, 1) :- !.
fib(1, 1) :- !.
fib(N, F) :-
        fib(1,1,1,N,F).

fib(_F, F1, N, N, F1) :- !.
fib(F0, F1, I, N, F) :-
        F2 is F0+F1,
        I2 is I + 1,
        fib(F1, F2, I2, N, F).

A.35.2 Example 2: avoiding non-termination

SLD resolution easily results in an infinite loop due to left recursion, a goal that (indirectly) calls a variant of itself or cycles in the input data. Thus, if we have a series of connection/2 statements that define railway connections between two cities, we cannot use the most natural logical definition to express that we can travel between two cities:

% :- use_module(library(tabling)).
% :- table connection/2.

connection(X, Y) :-
        connection(X, Z),
        connection(Z, Y).
connection(X, Y) :-
        connection(Y, X).

connection('Amsterdam', 'Schiphol').
connection('Amsterdam', 'Haarlem').
connection('Schiphol', 'Leiden').
connection('Haarlem', 'Leiden').

After enabling tabling however, the above works just fine as illustrated in the session below. Where is the magic and what is the price we paid? The magic is, again, the fact that new goals to the tabled predicate suspend. So, all recursive goals are suspended. Eventually, a table for connection('Amsterdam', X) is created with the two direct connections from Amsterdam. Now, it resumes the first clause using the tabled solutions, continuing the last connection/2 subgoal with connection('Schiphol', X) and connection('Haarlem', X). These two go through the same process, creating new suspended recursive calls and creating tables for the connections from Schiphol and Haarlem. Eventually, we end up with a set of tables for each call variant that is involved in computing the transitive closure of the network starting in Amsterdam. However, if the Japanese rail network would have been in our data as well, we would not have produced tables for that.

1 ?- connection('Amsterdam', X).
X = 'Haarlem' ;
X = 'Schiphol' ;
X = 'Amsterdam' ;
X = 'Leiden'.

Again, the fact that a simple table/1 directive turns the pure logical specification into a fairly efficient algorithm is a clear advantage. Without tabling the program needs to be stratified, introducing a base layer with the raw connections, a second layer that introduces the commutative property of a railway (if you can travel from A to B you can also travel from B to A and a final layer that realises transitivity (if you can travel from A to B and from B to C you can also travel from A to C). The third and final layer must keep track which cities you have already visited to avoid traveling in circles. The transformed program however uses little memory (the list of already visited cities and the still open choices) and does not need to deal with maintaining consistency between the tables and ground facts.

A.35.3 Mode directed tabling

Tabling as defined above has a serious limitation. Although the definition of connection/2 from section section A.35.2 can compute the transitive closure of connected cities, it cannot provide you with a route to travel. The reason is that there are infinitely many routes if there are cycles in the network and each new route found will be added to the answer table and cause the tabled execution's completion algorithm to search for more routes, eventually running out of memory.

The solution to this problem is called mode directed tabling or answer subsumption.184The term answer subsumption is used by XSB and mode directed tabling by YAP and B-Prolog. The idea is that some arguments are considered `outputs', where multiple values for the same `input' are combined. Possibly answer aggregation would have been a better name. In this execution model one or more arguments are not added to the table. Instead, we remember a single aggregated value for these arguments. The example below is derived from section A.35.2 and returns the connection as a list of cities. This argument is defined as a moded argument using the lattice(PI) mode.185This mode is compatible to XSB Prolog. This causes the tabling engine each time that it finds an new path to call shortest/3 and keep the shortest route.

:- use_module(library(tabling)).
:- table
    connection(_,_,lattice(shortest/3)).

shortest(P1, P2, P):-
    length(P1, L1),
    length(P2, L2),
    (   L1 < L2
    ->  P = P1
    ;   P = P2
    ).

connection(X, Y, [X,Y]) :-
    connection(X, Y).
connection(X, Y, P) :-
    connection(X, Z, P0),
    connection(Z, Y),
    append(P0, [Y], P).

The mode declation scheme is equivalent to XSB with partial compatibility support for YAP and B-Prolog. The lattice(PI) mode is the most general mode. The YAP all (B-Prolog @) mode is not yet supported. The list below describes the supported modes and indicates the portability.

Var
+
index
A variable (XSB), the atom index (YAP) or a + (B-Prolog) declare that the argument is tabled normally.
lattice(PI)
PI must be the predicate indicator of a predicate with arity 3. On each answer, PI is called with three arguments: the current aggregated answer and the new answer are inputs. The last argument must be unified with a term that represents the new aggregated answer. In SWI-Prolog the arity (3) may be omitted. See the example above.
po(PI)
Partial Ordening. The new answer is added iff call(PI, +Old, +Answer) succeeds. For example, po('<'/2) accumulates the largest result. In SWI-Prolog the arity (2) may be omitted, resulting in po(<).
-
first(first)
he atom - (B-Prolog) and first (YAP) declare to keep the first answer for this argument.
last
The atom last (YAP) declares to keep the last answer.
min
The atom min (YAP) declares to keep the smallest answer according to the standard order of terms (see @</2). Note that in SWI-Prolog the standard order of terms orders numbers by value.
max
The atom max (YAP) declares to keep the largest answer according to the standard order of terms (see @>/2). Note that in SWI-Prolog the standard order of terms orders numbers by value.
sum
The atom sum (YAP) declares to sum numeric answers.

A.35.1 Tabling predicate reference

table +PredicateIndicators
Prepare the given PredicateIndicators for tabling. Can only be used as a directive. 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.

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.
Errors
permission_error(abolish, table, all) if tabling is in progress.
[det]abolish_table_subgoals(:Subgoal)
Abolish all tables that unify with SubGoal.

A.35.1.1 About the tabling implementation

The SWI-Prolog implementation uses Delimited continuations (see section 4.10 to realise suspension of variant calls. The initial version was written by Benoit Desouter and described in Desouter et al., 2015. We moved the main data structures required for tabling, the answer tables (see section 4.14.4) and the worklist to SWI-Prolog's C core. Mode directed tabling (section A.35.3) is based on a prototype implementation by Fabrizio Riguzzi.

The table/1 directive causes the creation of a wrapper calling the renamed original predicate. For example, the program in section A.35.2 is translated into the following program. We give this information to improve your understanding of the current tabling implementation. Future versions are likely to use a more low-level translation that is not based on wrappers.

connection(A, B) :-
        start_tabling(user:connection(A, B),
                      'connection tabled'(A, B)).

'connection tabled'(X, Y) :-
        connection(X, Z),
        connection(Z, Y).
'connection tabled'(X, Y) :-
        connection(Y, X).

'connection tabled'('Amsterdam', 'Schiphol').
'connection tabled'('Amsterdam', 'Haarlem').
'connection tabled'('Schiphol', 'Leiden').
'connection tabled'('Haarlem', 'Leiden').

A.35.1.2 Status of tabling

The current implementation is merely a first prototype. It needs several enhancements before we can consider it a serious competitor to Prolog systems with mature tabling such as XSB, YAP and B-Prolog. In particular,

  • The performance needs to be improved.
  • Memory usage needs to be reduced.
  • Tables must be shared between threads, both to reduce space and avoid recomputation.
  • Tables must be invalidated and reclaimed automatically.
  • Notably XSB supports incremental tabeling and well-founded semantics under negation.

ClioPatria (version V3.1.1-21-gb8003bb)