More advanced Prolog
Constructing and decomposing terms
/* arg(+N,+Term,?Arg) is true if Arg is the Nth argument of Term.
It is used either to find a particular item in a compound term
or to instantiate a variable argument of a term. */
?-arg(1,color(red),X).
X=red
?-arg(1,color(X),yellow).
X=yellow
/* functor(+Term,?F,?Arity) or functor(?Term,+F,+Arity)
is true if Term is a term whose functor has name F and
arity Arity. It is used either to find the functor name
and its arity in a given term or to build a term with a
particular functor name and arity: */
?- functor(color(x),F,N).
F = color,
N = 1
?- functor(X,color,1).
X = color(_A)
/* the univ predicate
=.. is defined as +Term=..?List or ?Term=..+List
Used to create a list from a predicate term, as in
foo(a,b,c)=..Y where Y is unified with [foo,a,b,c]
or to create a predicate term from a list, as in
X=..[foo,a,b,c] where X is unified with foo(a,b,c)
*/
/* example of use of =..
This checks if all elements of a list satisfy a property.
The property is expressed as a unary predicate. */
satisfy([],_).
satisfy([X|L],P):- R=..[P,X], R, satisfy(L,P).
color(red).
color(green).
color(blue).
?- satisfy([red,blue,green],color).
yes
?- satisfy([red,yellow],color).
no
/* call(X) or simply X allows executing a predicate that can be passed
as an argument to another predicate. */
?- Goal=..[member,a,L],Goal.
G = member(a, [a|_G367])
L = [a|_G367] ;
G = member(a, [_G366, a|_G370])
L = [_G366, a|_G370] ;
G = member(a, [_G366, _G369, a|_G373])
L = [_G366, _G369, a|_G373]
Yes
/* this and =.. come handy to define a map predicate, which applies its first
argument to each element of a list and returns a list of results */
map(F,[],[]):-!.
map(F,[X|Y],[U|V]):- T=..[F,X,U], T, map(F,Y,V).
double(X,Y):- Y is 2*X.
?- map(double,[1,2,3],L2).
L2 = [2, 4, 6]
/* clause(A,B) retrieves a clause whose head matches A and body matches B
If the clause has no body (i.e. it is a fact) the value of Body is
True. */
?- clause(member(X,L),Body)
X = _G256
L = [_G256|_G397]
Body = true ;
X = _G256
L = [_G399|_G400]
Body = member(_G256, _G400) ;
no
Setof, bagof, and findall
/* bagof(?Template, +Goal, ?Bag) is true if Bag is the bag of
all the instances of Template for which Goal is true.
If no solutions are found it fails */
?- Input=[1,2,3],
bagof((Left, Right), append(Left, Right, Input), Bag).
Bag = [([],[1,2,3]),([1],[2,3]),([1,2],[3]),([1,2,3],[])],
Input = [1,2,3] ? ;
no
/* setof(?Template, +Goal, ?Set)
Set is the set of all instances of Template such that Goal
is satisfied when the set is non empty. Goal is a goal or
set of goals (as in call(Goal)), Set is a set of terms
represented as a list without duplicates in the standard
order for terms. If no solutions are found it fails */
likes(bill,cider).
likes(dick,beer).
likes(harry,beer).
likes(ian,cider).
likes(tom,beer).
likes(tom,cider).
?- setof(X, likes(X,Y), S).
S=[dick,harry,tom],
Y=beer ? ;
S=[bill,ian,tom],
Y=cider ? ;
no
?- setof(X, Y^likes(X,Y), S).
S=[bill,dick,harry,ian,tom] ? ;
no
/* The _ produces the same results as when using the variable Y */
?- setof(X, likes(X,_), S).
S = [dick,harry,tom] ? ;
S = [bill,ian,tom] ? ;
no
?- setof((Y,S), setof(X, likes(X,Y), S), SS).
SS = [(beer,[dick,harry,tom]),(cider,[bill,ian,tom])] ? ;
no
?- setof(X, (member(X,[1,2,2]), X>1),L).
L=[2];
no
/* findall(?Template, +Goal, ?Bag)
Bag is a list of instances of Template in all proofs of Goal found
by Prolog. The list may be empty, all variables are considered as
being existentially quantified. Each invocation of findall/3 succeeds
once and no variables in Goal get bound. */
?- findall(X, likes(X,Y),S).
S = [bill,dick,harry,ian,tom,tom] ? ;
no
Challenge problem
What do you find incorrect in the following program? This is not trivial
(hint: it requires understanding how unification works with lists)
[Taken from Peter Ross, Advanced Prolog: techniques and examples,
Addison Wesley, 1989.]
% intersect/3: given two lists, finds their intersection
% that is, fidn all the members of the first list which also
% appear in the second list. If the lists contain no duplicates
% then this computes set intersection
% intersect(+L1, +L2, ?Result)
intersect([],_,[]).
intersect([H|T],L,[H|Rest]):- member(H,L),!,intersect(T,L,Rest).
intersect([_|T],L,L1]):- intersect(T,L,L1).