Project "Contraintes" Prolog Web Pages: Database Updates

Standard Prolog contains four built-in predicates which may modify the database:

A problem arises if one of these predicates is activated during a query. Since this potentially changes the clauses that are available to be chosen at a given choice point.

The standard adopts the ``logical'' database update viewpoint. In this view retracted clauses remain as choice points for the query but not the appended ones. Thus a query of the form.

setof(X, foo(X), S)
where foo/1 does something like foo(X) :- foo1(X), X1 is X + 7, assertz(foo(X1)).

will evaluate the setof/3 for the value of the database of foo/1 as it is at the beginning of the query, ignoring the added clauses.

Two examples

Compare the two predicates go/0 and go1/0

% test of successive retracts go :- retract(foo(X)), once((write(X),X1 is X +1, assertz(foo(X1)), nl)), fail. go. :- dynamic(foo/1). foo(1). foo(2). go1 :- retract(foo(X)), once((write(X),X1 is X +1, assertz(foo(X1)), nl)), go1. go1. go1/0 loops forever. Whereas go/0 terminates!

Since in practice this may be counter intuitive it is as well to observe the following rules, (taken from the book of Deransart, Ed-Dbali and Cervoni.

  1. asserta/1 may be used without restriction, (the added branch is already passed).
  2. Never use assertz/1 or retract/1 in an active predicate except to retract already used clauses.
  3. Never use abolish/1 on a predicate which is active.

Justifying the logical view

Since for some the logical update view is somewhat unexpected. It is worth giving some justification for the choice made by the ISO working group. There are two principal reasons for choosing the logical view:

  1. It is easier to reason about programs that take this approach;
  2. The alternative -- the immediate view -- has a much less comprehensible semantics. Indeed the inconsistencies among the implementations that used this view were significant.

To see why it is easier to reason about a program when the logical update view is in force. Observe that the search tree has the property that when a node is first reached it is possible to determine the number of children that the node has. This is not possible using the immediate view since any (dynamic) predicate might acquire additional clauses. This raises the question of whether a node that is closed (meaning all its children have been visited) can possible be reopened by an assert. Worse what if a retract cuts off the very branch which is currently being explored?

For more on the semantics of updates to the Prolog database see:

E. Boerger, B. Demoen `A framework to specify database update views for Prolog' Proceedings of the Third International Symposium on Programming Language Implementation and Logic Programming Passau, August 1991, pp. 147-158



Author: J.P.E. Hodgson
Saint Joseph's University
Philadelphia PA 19131
USA


Last Changed: 1 january 2003