Prolog Overview

References

SWI-Prolog.

Learn Prolog Now

Basics

A Prolog program (called a knowledge base (KB)) defines one or more relationships using facts and rules.

Here's an example:

male(homer).
male(bart).

female(marge).
female(lisa).
female(maggie).

parent(homer, bart).
parent(homer, lisa).
parent(homer, maggie).
parent(marge, bart).
parent(marge, lisa).
parent(marge, maggie).

mother(X, Y) :- parent(X, Y), female(X).
father(X, Y) :- parent(X, Y), male(X).
son(X, Y) :- parent(Y, X), male(X).
daughter(X, Y) :- parent(Y, X), female(X).

This KB defines two unary relationships: male and female, and five binary relationships: parent, mother, father, son, and daughter.

Note that the name of a relationship (also called a predicate or functor) must begin with a lowercase letter.

Also note that all facts, rules, and queries end with a period.

The male, female, and parent relationships are defined using facts-- simple assertions that state that certain elements are in the relationship:

parent(homer, bart).

Elements can be numbers, strings, constants or structures. Constants begin with lowercase letters, strings are bracketed by single quotes. For example:

quote(ceasar, 'et tu Brutus?').

The remaining relationships are defined using rules.

For example, the last rule asserts that X is the daughter of Y, if Y is the parent of X and X is female.

X and Y are variables. Variables begin with uppercase letters.

We can translate ":-" as "if", comma as "and".

Here's a sample session with a Prolog interpreter:

1 ?- male(homer).
true.

2 ?- male(lisa).
false.

3 ?- male(luke).
false.

4 ?- female(X).
X = marge |    ;
X = lisa |    ;
X = maggie.

5 ?- parent(marge, lisa).
true |    ;
false.

6 ?- daughter(lisa, X).
X = homer |    ;
X = marge |    ;
false.

Queries are typed by the user. The first three queries ask if homer, lisa, and luke are males. Surprisingly, Prolog claims that luke is not a male. This is because the fact that luke is a male cannot be inferred from the KB.

The fourth query begins to show the power of Prolog. The query asks for all substitutions for the variable X that are female. Each time the user types a semicolon, Prolog finds another valid substitution.

How does it work?

At any given moment the Prolog engine (interpreter) has a list of goals it is trying to satisfy. When all of the goals have been removed from the list, the engine is done and returns true or any bindings that it created in order to satisfy the goals.

Initially, the goals list only contains the user's query.

To remove the first goal in the list, the engine searches the KB looking for a fact that matches the goal. If one is found, then the goal is removed from the list.

If the engine finds a rule with a head that matches the goal, then the goal is removed, but the conditions in the tail of the rule are added to the goal list. This is called resolution.

The Prolog engine uses a sophisticated pattern matching algorithm called unification to match goals to facts and rules. Unification may produce substitutions of variables by literals in order to create a match. For example, the query male(X) matches the fact male(bart) if we make the binding X = bart.

Because a relationship might be defined by many facts and rules, the Prolog interpreter may need to unify a goal with many of these before it finds the right one. This is called backtracking.

We can interpret the above as an attempt by Prolog to refute the negation of a goal. Failure to refute the negation of a goal can be interpreted as a proof of the goal from the KB.

Math in Prolog

Defining a mathematical function in Prolog means defining a relationship between the function and its return value. For example, here's the definition in C of a function that converts centigrade temperatures to Fahrenheit temperatures:

double c2f(double c) { return 9 * c / 5 + 32; }

Here's the equivalent definition in Prolog:

c2f(C, F) :- F is 9 * C / 5 + 32.

Basically, this definition says that if the input to c2f is C, then the output will be F.

Here's a sample session:

15 ?- c2f(100, X).
X = 212.

16 ?- c2f(0, X).
X = 32.

17 ?- c2f(37, X).
X = 98.6.

18 ?- c2f(-40, X).
X = -40.

19 ?- c2f(X, 70).
ERROR: is/2: Arguments are not sufficiently instantiated

 

Notice the error when we attempted to invert the function. This happens because "is" is a special one-way operation in Prolog that computes what is on its right and assigns it to what is on the left:

20 ?- X is 6 * 7.
X = 42.

21 ?- 6 * 7 is X.
ERROR: is/2: Arguments are not sufficiently instantiated

Of course we can define recursive relationships in Prolog. Here's the good old factorial function:

fact(0, 1).
fact(N, F) :- N > 0, N1 is N - 1, fact(N1, F1), F is N * F1.

The basic rule of thumb is never to write as the leftmost goal of the tail something that is identical (modulo variable names) with the goal given in the head. Rather, place such goals (which trigger recursive calls) as far as possible towards the right of the tail. That is, place them after the goals which test for the various (non-recursive) termination conditions.

For example, the following recursive definitions make sense logically, but lead to infinite loops:

fact(N, F) :- N > 0, N1 is N - 1, fact(N1, F1), F is N * F1.
fact(0, 1).

fact(0, 1).
fact(N, F) :- fact(N1, F1), N > 0, N1 is N - 1, F is N * F1.

Defining symmetric relations in Prolog

Consider the Prolog program:

road(sf, la).
road(sf, portland).
road(la, denver).
road(denver, nyc).
road(chicago, denver).

road(X, Y) :- road(Y, X).

Obviously if there is a road from Chicago to Denver, then the same road connects Denver back to Chicago (unless it's one-way). To save the work of adding a bunch more facts like:

road(denver, chicago)

I simply created a rule that says the road relationship is symmetric. This makes sense logically, but computationally it leads the Prolog interpreter into an infinite loop:

road(sf, Y)
road(Y, sf)
road(sf, Y)
road(Y, sf)
etc.

To avoid this we introduce a new relationship as the symmetric closure of road:

roadTo(X, Y) :- road(X, Y); road(Y, X).

Note that semi-colon means "or". This could be rewritten as two rules:

roadTo(X, Y) :- road(X, Y).
roadTo(X, Y) :- road(Y, X).

Defining transitive relations in Prolog

The following KB is meant to define the prerequisite graph from a course catalog.

prereq(cs152, cs151).
prereq(cs151, cs46B).
prereq(cs46B, cs46A).
prereq (X, Y) :- prereq(X, Z), prereq(Z, Y).

The prerequisite relationship is transitive, meaning that if A is a prerequisite of B and B is a prerequisite of C, then A is a prerequisite of C. So the last rule makes sense, but computationally it leads the Prolog interpreter into another infinite loop:

prereq(cs152, X)
prereq (X, Y)
prereq(cs152, Z)
prereq (X, Y)
prereq(cs152, Z)
prereq (X, Y)
prereq(cs152, Z)
etc.

To fix this problem define prerequisite as the transitive closure of a simpler relationship:

prerequisite (X, Y) :- prereq(X, Y).
prerequisite (X, Y) :- prereq(X, Z), prerequisite(Z, Y).

Structures

A structure looks like a fact, but it is used as a term representing a composite element.

For example, the following fact asserts that Bill Smith is employed by IBM:

employedBy(ibm, employee(bill, smith, date(9, 15, 1960))).

Instead of using a simple constant to represent Smith, an employee structure is used with fields corresponding to Smith's first name, last name, and date of birth. Note that the date is also a structure with fields corresponding to month, day, and year.

This enables complex queries such as:

employedBy(ibm, employee(FN, LN, date(9, DAY, YEAR))).

This will list all IBM employees born in September.

Labs

Lab

Create a KB called sjsu that contains the following information:

Turing is the instructor for CS152. Godel, Escher, Bach, and VonNeumann are enrolled in CS152.

Create a rule that defines the relationship Instructor X teaches student Y.

Lab: Recursion

Create and test a knowledge bases for the following scenario.

Homer is the parent of Bart, Lisa, and Maggie. Abe and Mona are Homer's parents.

Marge is also the parent of Bart, Lisa, and Maggie. Clancy and Jacquelin are her parents.

Clancy and Jacquelin are also the parents Selma and Patty.

Parents are ancestors as are ancestors of parents.

Siblings share a parent.

Lab: Arithmetic

We can use structures to represent positive integers in Prolog. For example:

0 = zero
1 = inc(zero)
2 = inc (inc (zero))
3 = inc (inc (inc (zero)))
etc.

Here inc(x) stands for the increment (add one) function.

Define and test the predicate add(X, Y, Z), which represents the relationship Z = X + Y.

Here's a start:

add(zero, X, ???).

add(inc(X), Y, inc(Z)) :- ???.

Define and test the predicate mul(X, Y, Z) which represents the relationship Z = X * Y.

Define and test the predicate exp(X, Y, Z) which represents the relationship Z = X ^ Y.

Define and test the predicate less(X, Y), which represents the relationship X < Y.

Lab: Org Charts, etc.

Define and test the following predicates:

supervises(X, Y) which represents the relationship X supervises Y or a supervisor of Y.

friend(X, Y) which represents the relationship X is a FB friend of Y.

equals(X, Y) which represents the relationship X == Y.

distance(X, Y, Z) which represents the relationship the distance from X to Y is Z hops where X and Y are nodes on an Ethernet wire.

Lab: Evaluating expressions

We can use structures to represent syntax trees in Prolog. For example, the expression

(3 * 4) + (5 + 6)

can be represented by the syntax tree:

sum(prod(num(3), num(4)), sum(num(5), num(6)))

Write an evaluator for the language of sums and products:

?- eval(sum(prod(num(3), num(4)), sum(num(5), num(6))), X).
X = 23.

Lab: Trees

Implement height(Tree, H) where H is the height of a tree of the form leaf or parent(LeftChild, RightChild)

Lab: Proplog

Proplog is a simplified version of Prolog that doesn't allow variables. Here's an example f a Proplog KB:

homerIsMale
bartIsMale
homerIsParentOfBart
homerIsFatherOfbart :- homerisParentOfBart, homerIsMale

Here's a sample session with a Proplog interpreter:

?- homerIsMale
true
?- lisaIsMale
false
?- homerIsFatherOfBart
true
?- quit
bye

Here's the design of the Proplog interpreter:



Here's a partial implementation:

Engine.java

Complete and test the implementation.