Prolog
introduction
What is Prolog?
- Prolog - Programming in Logic.
- A compiled, Untyped, declarative language.
- Originally developed for AI applications.
- First released in the 1970s.
Logic/Declarative Programming
Common use cases include:
- Database queries.
- Rule-based systems.
- Automated Reasoning.
In general - any problem that can be easily expressed in terms of logic or a set of constraints.
Advantages
- Concise and readable code.
- Easy to express complex problems.
- Modular and Extensible.
Disadvantages
- Not suitable for all problems.
- Usually not as performant as other languages.
Using Prolog
A Prolog program consists of a set of facts and rules. Given a program, we can make queries about these rules using a REPL.
In this class we will use Swi-Prolog.
Typical Workflows
Usually we will use Prolog in one of two ways:
- Open the REPL over a program and make queries.
- Dynamically add facts and rules (or even load programs) using the REPL.
Terms
Terms are the basic building blocks of Prolog programs.
Analogous to expressions in other languages.
terms - atoms
the simplest term is an atom, the following are atoms:
john
$<@
'an atom'
String atoms
- A string of letters, digits, and an underscore starting with a lower-case letter:
anna
x_25
nil
- A string of special characters (
+ - * / < > = : . & _ ~
):$<@
<---->
.:.
- A string of characters enclosed in single quotes:
'Tom'
'2A$'
Numeric atoms
- Integers:
123
-42
- Real numbers:
3.14
-0.573
2.4e3
Variables
A variable is a string of letters, digits and an underscore starting with an upper-case letter or an underscore
X_25
_result
compound terms
A compound term comprises a functor and arguments.
course(236319, pl)
A functor f
of arity n
is denoted f/n
.
A fact is a term that we define to be true in our program.
eats(bunny, carrot).
This fact states that the predicate eats
holds for the atoms bunny
and carrot
terms.
Facts can have any arity:
summer.
sad(john).
plus(2, 3, 5).
A finite set of facts constitutes a program:
mammal(rat).
mammal(bear).
fish(salmon).
eats(bear, honey).
eats(bear, salmon).
eats(rat, salmon).
eats(salmon, warm).
Facts can contain variables:
likes(X, course236319).
Variables are universally quantified, so this fact is equivalent to:
\[\forall X: likes(X, course236319)\]queries
A query is a conjunction of goals:
?- eats(X, salmon), eats(X, honey).
Variables are existentially quantified, so this query is equivalent to:
\[\exists X,eats(X, salmon) \land eats(X, honey)\]rules
A rule is a statement which enables us to define new relationships in terms of existing ones:
predicate(term1, ..., termN) :- goal1, ..., goalN.
Y
is a survival dependency of X
if:
X
eatsY
- or
X
eatsZ
andY
is a survival dependency ofZ
survival_dependency(X, Y) :- eats(X, Y).
survival_dependency(X, Y) :-
eats(X, Z), survival_dependency(Z, Y).
?- survival_dependency(bear, X).
dynamically loading programs
Given a program in a file prog.pl
we can load it into the REPL using consult/1
:
?- consult('prog.pl').
/* or */
?- consult(prog).
Also possible using brackets:
?- [prog].
matching
Two terms match if:
- They are identical.
- The variables in both terms can be instantiated to make the terms identical.
The =
operator performs matching
?- course(N, S, 95) = course(X, fall, G).
?- course(N, S, 95) = course(Y, M, 96).
?- course(X) = semester(Y).
matching rules
Terms S
and T
match if:
S
andT
are the same atom.S
andT
are the same number.- If one is a variable which is instantiated to the other.
- If
S
andT
are compound terms, they match iff:- They have the same functor and arity.
- All their corresponding arguments match.
- The variable instantiations are compatible.
geometric example
Use compound terms to represent geometric shapes.
point(1, 1)
seg( point(1, 1), point(2, 3) )
triangle( point(4, 2), point(6, 4), point(7, 1) )
geometric example
?- triangle(point(1, 1), A, point(2, 3))
=
triangle(X, point(4, Y), point(2, Z)).
matching as means of computation
Facts:
vertical(seg(
point(X, Y1),
point(X, Y2)
)).
Queries:
?- vertical(seg(point(1, 1), point(1, 2))).
?- vertical(seg(point(1, 1), point(2, Y))).
?- vertical(seg(point(2,3), P)).
arithmetic operations
- The operators
+ - * / div mod
are (infix) binary relations. - But they are considered arithmetic operators after the operator
is
.
?- X = 1 + 2.
?- X is 1 + 2.
comparison operators
X > Y
X < Y
X >= Y
X =< Y
X =:= Y % equal
X =\= Y % not equal
The comparison operators also force evaluation:
?- 11 * 6 = 66.
?- 11 * 6 =:= 66.
=
VS. =:=
=
is used for matching and may instantiate variables.=:=
causes an arithmetic evaluation of its operands and cannot instantiate variables.
?- 1 + X = Y + 2.
?- 1 + X =:= Y + 2.
Example - GCD
gcd(X, X, X).
gcd(X, Y, D) :-
X < Y,
Y1 is Y - X,
gcd(X, Y1, D).
gcd(X, Y, D) :-
Y < X,
gcd(Y, X, D).
?- gcd(12, 30, D).
builtin control predicates
conjunction ,/2
The goal (G1, G2)
succeeds if G1
and G2
succeed.
disjunction ;/2
The goal (G1 ; G2)
succeeds if G1
or G2
succeed.
Defined as follows:
(G1 ; G2) :- G1.
(G1 ; G2) :- G2.
true
The predicate true/0
always succeeds.
false
The predicates false/0
and fail/0
always fail.
negation as failure
- The negation predicate is
\+/1
. - It is not logical negation!
- For known predicates, prolog works under a closed world assumption - if something can’t be proved then it is false.
person(jimmy).
person(cindy).
?- person(rick).
?- \+ person(rick).
It might not work like you’d expect
?- person(X).
?- \+ person(X).
Why doesn’t prolog answer with X = rick
or simply with true
?
person(X)
succeeds so its negation fails
- if
G
fails\+ G
succeeds - if
G
succeeds\+ G
fails
\+/1
allows for non-monotonic reasoning - a fact can become false by adding clauses to the database:
illegal(murder).
legal(X) :- \+ illegal(X).
illegal(theft).
?- legal(theft).
exercise - family tree
Given a database with the following predicate:
parent(X, Y). % X is Y's parent
% examples:
parent(adam, cain).
parent(eve, cain).
parent(cain, enoch).
Define a predicate grandparent(X)
that holds when X
is a grandparent.
...
?- grandparent(X).
grandparent(X) :- parent(X, Y), parent(Y, _).
Define a predicate nuclear(X, Y)
that holds when X
and Y
are in the same nuclear family.
A nuclear family (in our example) consists of 2 parents and their common children.
...
?- nuclear(adam, X).
nuclear(X, Y) :- % siblings
parent(P1, X), parent(P2, X),
parent(P1, Y), parent(P2, Y),
\+(P1 = P2). % alternatively: `P1 \= P2`
nuclear(X, Y) :-
parent(X, C), parent(Y, C).
nuclear(X, Y) :-
(parent(X, Y); parent(Y, X)).
exercise - binary trees
We represent binary trees as terms:
nil
is the empty tree.node(N, Tl, Tr)
is a tree node whereN
is some number andTl
andTr
are binary trees.
Define a predicate tree_size(T, S)
such that T
is a binary tree and S
is its size
...
?- tree_size(node(1,
node(2,
nil,
nil
),
node(3,
node(4, nil, nil),
nil
)),
S).
tree_size(nil, 0).
tree_size(node(_, Tl, Tr), S) :-
tree_size(Tl, Sl),
tree_size(Tr, Sr),
S is Sl + Sr + 1.
Define a predicate tree_max(T, M)
such that T
is a binary tree and M
is the max of the values of T
’s nodes.
You may use the arithmetic function max/2
...
?- tree_max(node(10,
node(-3,
nil,
nil
),
node(14,
node(4, nil, nil),
nil
)),
M).
tree_max(node(N, nil, nil), N).
tree_max(node(N, nil, Tr), M) :-
tree_max(Tr, Mr), M is max(N, Mr).
tree_max(node(N, Tl, nil), M) :-
tree_max(Tl, Ml), M is max(N, Ml).
tree_max(node(N, Tl, Tr), M) :-
tree_max(Tl, Ml),
tree_max(Tr, Mr),
M is max(N, max(Ml, Mr)).
A perfect binary tree is a binary tree in which all interior nodes have two children and all leaves have the same depth. Also, the value of each interior node is equal to its depth.
Define a predicate perfect_tree(T, H)
such that T
is a perfect binary tree and H
is its height.
...
?- perfect_tree(T, 2).
perfect_tree(nil, 0).
perfect_tree(node(H, Tl, Tl), H) :-
H > 0,
H1 is H - 1,
perfect_tree(Tl, H1).