Home Contents Index Summary Previous Next

3.6 Control Predicates

The predicates of this section implement control structures. Normally these constructs are translated into virtual machine instructions by the compiler. It is still necessary to implement these constructs as true predicates to support meta-calls, as demonstrated in the example below. The predicate finds all currently defined atoms of 1 character long. Note that the cut has no effect when called via one of these predicates (see !/0).

one_character_atoms(As) :- findall(A, (current_atom(A), atom_length(A, 1)), As).

fail
Always fail. The predicate fail/0 is translated into a single virtual machine instruction.

true
Always succeed. The predicate true/0 is translated into a single virtual machine instruction.

repeat
Always succeed, provide an infinite number of choice points.

!
Cut. Discard choice points of parent frame and frames created after the parent frame. Note that the control structures ;/2, |/2, ->/2 and \+/1 are normally handled by the compiler and do not create a frame, which implies the cut operates through these predicates. Some examples are given below. Note the difference between t3/1 and t4/1. Also note the effect of call/1 in t5/0. As the argument of call/1 is evaluated by predicates rather than the compiler the cut has no effect.

t1 :- (a, !, fail ; b). % cuts a/0 and t1/0
t2 :- (a -> b, ! ; c). % cuts b/0 and t2/0
t3(G) :- a, G, fail. % if `G = !' cuts a/0 and t1/1
t4(G) :- a, call(G), fail. % if `G = !' cut has no effect
t5 :- call((a, !, fail ; b)). % Cut has no effect
t6 :- \+(a, !, fail ; b).% cuts a/0 and t6/0

+Goal1 , +Goal2
Conjunction. Succeeds if both `Goal1' and `Goal2' can be proved. It is defined as (this definition does not lead to a loop as the second comma is handled by the compiler): Goal1, Goal2 :- Goal1, Goal2.

+Goal1 ; +Goal2
The `or' predicate is defined as: Goal1 ; _Goal2 :- Goal1. _Goal1 ; Goal2 :- Goal2.

+Goal1 | +Goal2
Equivalent to ;/2. Retained for compatibility only. New code should use ;/2. Still nice though for grammar rules.

+Condition -> +Action
If-then and If-Then-Else. The ->/2 construct commits to the choices made at its left-hand side, destroying choice-points created inside the clause (by ;/2), or by goals called by this clause. Unlike !/0, the choicepoint of the predicate as a whole (due to multiple clauses) is not destroyed. The combination ;/2 and ->/2 is defines as: If -> Then; _Else :- If, !, Then. If -> _Then; Else :- !, Else. If -> Then :- If, !, Then.

Note that the operator precedence relation between ; and -> ensure If -> Then ; Else is actually a term of the form ;(->(If, Then), Else). The first two clauses belong to the definition of ;/2), while only the last defines ->/2.

+Condition *-> +Action ; +Else
This construct implements the so-called `soft-cut'. The control is defined as follows: If Condition succeeds at least once, the semantics is the same as (Condition, Action). If Condition does not succeed, the semantics is that of (Condition, Else). In other words, If Condition succeeds at least once, simply behave as the conjunction of Condition and Action, otherwise execute Else.

\+ +Goal
Succeeds if `Goal' cannot be proven (mnemonic: + refers to provable and the backslash (\) is normally used to indicate negation).