Guide to Prolog Programming

© Roman Barták, 1998

Home
Prolog in Examples
Prolog Data Structures
List Processing

Previous | Contents | Next

Sets in Prolog

Sets are powerfull data structure that can be naturally expressed using lists in Prolog. To improve efficiency of implementation we use ordered lists as representation of sets. Thus, we define the relations "less then" and "is list" on a following way:

list([]).
list([_|_]).
   
lt(X,Y):-var(X);var(Y).
lt(X,Y):-nonvar(X),nonvar(Y),X<Y.


Union, Intersection, Difference and Selection

Now, we add definitions for obvious set operations like union, intersection and difference. Note, how we exploit the order of set elements in following procedures.

union([],S,S).
union(S,[],S):-S\=[].
union([X|TX],[X|TY],[X|TZ]):-
   union(TX,TY,TZ).
union([X|TX],[Y|TY],[X|TZ]):-
   lt(X,Y),
   union(TX,[Y|TY],TZ).
union([X|TX],[Y|TY],[Y|TZ]):-
   lt(Y,X),
   union([X|TX],TY,TZ).
   
intersection([],S,[]).
intersection(S,[],[]):-S\=[].
intersection([X|TX],[X|TY],[X|TZ]):-
   intersection(TX,TY,TZ).
intersection([X|TX],[Y|TY],TZ):-
   lt(X,Y),
   intersection(TX,[Y|TY],TZ).
intersection([X|TX],[Y|TY],TZ):-
   lt(Y,X),
   intersection([X|TX],TY,TZ).
   
difference([],S,[]).
difference(S,[],S):-S\=[].
difference([X|TX],[X|TY],TZ):-
   difference(TX,TY,TZ).
difference([X|TX],[Y|TY],[X|TZ]):-
   lt(X,Y),
   difference(TX,[Y|TY],TZ).
difference([X|TX],[Y|TY],TZ):-
   lt(Y,X),
   difference([X|TX],TY,TZ).

We can also define a selection operation which selects elements satisfying a given condition from a set. Note, how we use the copy_term and call to test the condition. Also, we use if-then-else operation (Cond -> ThenBranch ; ElseBranch) to shorten the procedure.

select([],X,Cond,[]).
select([H|T],X,Cond,Sel):-
   copy_term(X-Cond,XC-CondC),
   H=XC,
   (call(CondC) -> Sel=[H|R] ; Sel=R),
   select(T,X,Cond,R).

If you do not fully understand the meaning and usage of selection operation try examples like the following one:

?-select([1,2,3,4],X,X>2,Result).


Subset and Membership

It is also possible to define natural relations between sets like subset and member. Again note the usage of element order that improves efficiency of the procedures.

subset([],V).
subset([H|T1],[H|T2]):-subset(T1,T2).
subset([H1|T1],[H2|T2]):- lt(H2,H1),subset([H1|T1],T2).
   
in(X,[X|T]).
in(X,[Y|T]):-lt(Y,X),in(X,T).


Operators for Sets

Finally, we define operators which help us to write set operations and relations in a natural way. Note the different priority of operators.

:-op(400,yfx,/-\).   % intersection
:-op(500,yfx,\-/).   % union
:-op(600,yfx,\).     % difference
:-op(700,xfx,is_set).
:-op(700,xfx,is_in).
:-op(700,xfx,is_subset).

Operation "is_set" evaluates the expression with sets. It corresponds to "is" operation in Prolog.

S is_set S1 \-/ S2 :-
   SS1 is_set S1,
   SS2 is_set S2,
   union(SS1,SS2,S).
S is_set S1 /-\ S2 :-
   SS1 is_set S1,
   SS2 is_set S2,
   intersection(SS1,SS2,S).
S is_set S1 \ S2 :-
   SS1 is_set S1,
   SS2 is_set S2,
   difference(SS1,SS2,S).
S is_set sel(X,Cond,Set):-
   SSet is_set Set,
   select(SSet,X,Cond,S).
S is_set S:- list(S).

We can also add the member and subset operations.

X is_in S :- SS is_set S, in(X,SS).
U is_subset V:- US is_set U, VS is_set V, subset(US,VS).

Ok, now we can use sets in an obvious way.

?- [1,2,3] /-\ [2,3,4] is_subset [1,2,3] \-/ [2,3,4].
?- S is_set ([1,2,3] \ [2,4,5] /-\ [2,6,7])\-/[2,3,6].
?- X is_in [1,2,3] \-/ [3,4,5].
...


Compact representation

The above representation of sets is satisfactory for small sets, but it is not enough efficient for large sets containing compact blocks. Thus, we offer following compact representation of sets:

set [1,2,3,4,5,7,8,9] is represented as [1...5,7...9]

To use this representation we define the "compact operator ..." first:

op(100,xfx,'...')

Ofcourse, we have to redefine the above procedures for union, intersection, difference, select, subset, and in.

c_in(X,[X|T]):-X\=A...B.
c_in(X,[A...B|T]):-in_interval(X,A,B).
c_in(X,[Y|T]):-Y\=A...B,lt(Y,X),c_in(X,T).
c_in(X,[A...B|T]):-lt(B,X),c_in(X,T).
   
in_interval(X,X,B).
in_interval(X,A,B):-nonvar(X),X=B.
in_interval(X,A,B):-nonvar(X),lt(A,X),lt(X,B).
in_interval(X,A,B):-var(X),lt(A,B),A1 is A+1,in_interval(X,A1,B).

Rewrite the other procedures as your homework.

The compact representation in conjunction with the powerfull select operation enable compact description of various sets.

sel(X,even(X),[1...100]) % set of even numbers between 1 and 100

Operators can improve readibility of Prolog programs.


Designed and maintained by Roman Barták

Previous | Contents | Next