Basic order of evaluation
In general, the list of facts and rules is searched top-down when trying
to resolve a query or goal.
When dealing with multiple subgoals, evaluation takes place left-to-right.
(Prolog programmers often make extensive use of the known search order to improve the efficiency of queries.)
The logical operators for combining subgoals are the comma for logical and,
the semi-colon for logical or, they not()
function for negation,
and brackets for grouping sets of goals. For example:
f(X,Y) :- g(X), (h(Y) ; h(X)), not(g(Y)).
An if-then operator is supplied, with the syntax X -> Y ; Z
meaning if X is true then evaluate to Y, otherwise evaluate to Z.
Unification and backtracking
During the process of trying to resolve a query or goal, unification is an
attempt to treat two items as the same thing.
For instance, suppose we have the fact tall(bob).
and a query
tall(X).
Unification is the step where we attempt to treat
X
and bob
as one and the same.
This is most important when there are multiple goals to be handled as part of query resolution. For instance, suppose we have the following facts
female(meg). % fact 0 male(stewie). % fact 1 male(chris). % fact 2 sibling(chris,stewie). % fact 3 sibling(A,B) :- sibling(B,A). % rule 1 brothers(X,Y) :- sibling(X,Y), male(X), male(Y). % rule 2 sisters(X,Y) :- sibling(X,Y), female(X), female(Y). % rule 3Now suppose we issue the query
brothers(M,N).
. The process of
resolving this query would look something like:
For example, suppose we added a new fact:
female(meg). male(stewie). male(chris). sibling(chris, meg). sibling(chris,stewie). sibling(A,B) :- sibling(B,A). brothers(X,Y) :- sibling(X,Y), male(X), male(Y). sisters(X,Y) :- sibling(X,Y), female(X), female(Y).Now we issue the same query,
brothers(M,N).
sibling(chris, meg).
which unifies X=M=chris and Y=N=meg
and leaves us with the two subgoals male(X=M=chris), male(Y=N=meg)
sibling(chris,meg)
).
We now undo the unification, leaving us back at X=M and Y=N.
sibling(chris,stewie)
which unifies X=M=chris and Y=N=stewie,
and from here the query would successfully proceed as in the first example.
true, fail, repeat, cuts
We can also manipulate how rules succeed or fail, and how/when
backtracking and unification take place using a variety of built in prolog
predicates.
The keyword true
is treated as a goal which always succeeds,
while the keyword fail
is treated as a goal which always fails.
(Later we will discuss situations in which such goals may prove useful.)
The keyword repeat
causes the goals to its right to be continually
repeated until they succeed, for instance:
playgame(Result) :- initializegame, repeat, getnextcommand(C), executecommand(C), testforgameend(Result).The cycle of getting a command from the player, running the command, and checking to see if the game was over would repeat until the game ended. Presumably
testforgameend
succeeds when the player has either won
or lost, and the result (win/loss/draw or whatever) would be unified with
Result
.
The cut operator is the exclamation mark: !
This is used to prevent backtracking beyond a certain point.
For example, suppose picknumbers(NumberList)
lets a player
pick lottery numbers, and checkforwinner(NumberList)
tests
to see if they won. Consider the following rule:
playlottery :- picknumbers(NumberList), checkforwinner(NumberList).
If we issue the query playlottery.
, and we pick a bad set of
numbers the first time (our numbers being unified with NumberList),
then when checkforwinner
fails the query would backtrack,
undo the unification, and give us a new chance to picknumbers
.
Since that probably isn't the desired behaviour, we want to ensure that once the player has picked their numbers they can never back up and undo that.
We place a cut symbol, !, after the picknumbers goal to indicate that once
they get that far they cannot back up.
playlottery :- picknumbers(NumberList), !, checkforwinner(NumberList).