Avoiding Creation of Backtrack Points

Since the creation of backtrack points is relatively expensive, program efficiency may be improved substantially by using constructs that avoid the creation of backtrack points where possible. The SB-Prolog compiler recognizes conditionals involving certain complementary inline tests, and generates code that does not create choice points for such cases. Two inline tests p(t1,…, tn) and q(t1,…, tn) are complementary if and only if p(t1,... , tn)≡$\em not$(q(t1,…, tn)). For example, the literals `X > Y' and `X = < Y' are complementary. At this point, complementary tests are recognized as such only if their argument tuples are identical. The inline predicates that are treated in this manner, with their corresponding complementary literals, are shown in Table [*].

Table: Complementary Tests Recognized by the Compiler
Inline Test Complementary Test
> /2 = < /2
= < /2 > /2
> = /2 < /2
< /2 > = /2
=:=/2 = \  = /2
= \  = /2 =:=/2
?=/2 \  = /2
\  = /2 ?=/2
var/1 nonvar/1
nonvar/1 var/1


The syntactic constructs recognized are:
(i)
Disjuncts of the form

$\displaystyle \em head$(…)$\displaystyle \tt :-$($\displaystyle \em test$(t1,…, tn),…);(not($\displaystyle \em test$(t1,…, tn),…)).

or

$\displaystyle \em head$(…)$\displaystyle \tt :-$($\displaystyle \em test$(t1,…, tn),…);(($\displaystyle \em comp\_test$(t1,…, tn),…)).

where test is one of the inline tests in the table above, and comp_test the corresponding complementary test (note that the arguments to test and comp_test have to be identical).

(ii)
Conditionals of the form

$\displaystyle \em head$$\displaystyle \tt :-$($\displaystyle \em test_{1}^{}$,…,$\displaystyle \em test_{n}^{}$) - > $\displaystyle \em True\_Case$;$\displaystyle \em False\_Case$.

or

$\displaystyle \em head$$\displaystyle \tt :-$($\displaystyle \em test_{1}^{}$;…;$\displaystyle \em test_{n}^{}$) - > $\displaystyle \em True\_Case$;$\displaystyle \em False\_Case$.

where each $\em test_{i}^{}$ is an inline test, as mentioned in the table above.

The code generated for these cases involves a test and conditional branch, and no choice point is created. We expect future versions of the translator to recognize a wider class of complementary tests.

Notice that this discourages the use of explicit cuts. For example, whereas a choice point will be created for


part(M,[E|L],U1,U2) :- 

((E =< M, !, U1 = [E|U1a], U2 = U2a) ;
(U1 = U1a, U2 = [E|U2a])),
part(M,L,U1a,U2a).
no choice point will be created for either

part(M,[E|L],U1,U2) :- 

(E =< M –>
(U1 = [E|U1a], U2 = U2a) ;
(U1 = U1a, U2 = [E|U2a])),
part(M,L,U1a,U2a).
or

part(M,[E|L],U1,U2) :- 

((E =< M, U1 = [E|U1a], U2 = U2a) ;
(E > M, U1 = U1a, U2 = [E|U2a])),
part(M,L,U1a,U2a).
Thus, either of the two later versions will be more efficient than the version with the explicit cut (this is a design decision we have consciously made, in the hope of discouraging blatantly non-declarative code where efficient declarative code can be written).