Core components
The basic elements of a Prolog "program" are
entities in Prolog are always written in lowercase letters, e.g.
fred
, or wilma
variables in Prolog always begin with an uppercase letter, e.g.
Individual
, or Thing
properties look like a C++ function call - the name of the property
then the entity that has that property is given in brackets, e.g.
carnivore(fred)
, or food(vegetables)
relationships in Prolog again look like a C++ function call,
we give the relationship name first, then in brackets the
two entities that are related, e.g.
eats(wilma,meat)
, eats(wilma,vegetables)
For example, a rule could state that if someone eats meat and they eat vegetables then they are an omnivore.
rules in Prolog have three parts:
omnivore(Individual)
Note that the entity here will usually be a variable.
:-
which separates the
result from the clauses
There are several logic symbols which can be used in the right hand side:
\+
in some ways functions like logical NOT,
but there are some important differences that we'll consider later,
and is more properly referred to as "not proven".
X -> Y ; Z
attempts X,Y if X is true but X,Z otherwise
(effectively if X is true then try Y else try Z)
Since an omnivore must eat meat and eat vegetables, our clauses
would look like
eats(Individual,meat),eats(Individual,vegetables)
In the omnivore example, the whole rule would look like:
omnivore(Individual) :-
eats(Individual,meat),eats(Individual,vegetables)
Recursive rules:
% factorial(N, F) is true if F = N! factorial(1,1). % rule to apply if we are given N as an integer F as a variable, % adding "local" new variables N1 and F1 factorial(N, F) :- integer(N), var(F), N>1, N1 is N-1, factorial(N1, F1), F is N*F1.
factorial(1,1): doesn't match factorial(N, F): try matching with N=3, X=F: 3 is an int, F is a var, N is > 1, set N1 to 2, call factorial(2,F1) factorial(1,1): doesn't match factorial(N, F): try matching with N=2, F1=F 2 is an int, F is a var, N is > 1, set N1 to 1, call factorial(1,F1) factorial(1,1): matches if we use F1=1, return success, with F1=1 set F is N*F1, i.e. 2*1, i.e. 2, return success, with F=2 set F is N*F1, i.e. 3*2, i.e. 6 return success, with F=6 done!
Emulating loops with recursion:
% loop(Current,Last) % ------------------ % for values from current up to and including last, % print the current value (one value per line) % the base case represents the last pass loop(Last,Last) :- number(Last), write_ln(Last). % the general case loop(Current,Last) :- number(Current), number(Last), Current =< Last, write_ln(Current), % the body of our loop Next is Current + 1, loop(Next, Last).So for a query like loop(3,5). we would get the following:
Covering all scenarios:
Consider the factorial computation above:
- it works if they supply N as a number and F as a variable
- it works if they supply N as a number and F as a number
- it fails if they supply N as a variable,
which we could fix with an extra set of rules:
factorial(N, F) :- integer(F), F > 1, var(N), % compute 1!, 2!, 3! etc until we N or exceed F factorial(N, F, 1, 1). % factorial(N,F,I,FI) % ------------------- % given I and FI = I!, we're computing I!, (I+1)!, ..., N! % until FI = F (success) or FI > F (fail) % base case 1, we found it factorial(N,F,N,F). % base case 2, FI is too big, give up factorial(_,F,_,FI) :- FI > F, !, fail. % general case, try recursively on I+1 and (I+1)! factorial(N,F,I,FI) :- NewI is I + 1, NewFI is FI * NewI, factorial(N,F,NewI,NewFI).