10.21 Unordered Set Operations—library(sets)

This library module provides operations on sets represented as unordered lists with no repeated elements. The ordered representation used in library(ordsets) is much more efficient, but these routines were designed before sort/2 entered the language. Exported predicates:

add_element(+Element, +Set1, -Set2)
is true when Set1 and Set2 are sets represented as unordered lists, and Set2 = Set1 U {Element}. It may only be used to calculate Set2 given Element and Set1.
del_element(+Element, +Set1, -Set2)
is true when Set1 and Set2 are sets represented as unordered lists, and Set2 = Set1 \ {Element}. It may only be used to calculate Set2 given Element and Set1. If Set1 does not contain Element, Set2 will be identical to Set1 (the old version made a new copy of Set1). If Set1 is not an unordered set, but contains more than one copy of Element, only the first will be removed. If you want to delete all copies of a given element, use lists:delete/3. For a version which fails if Element is not in Set1, use selectchk/3.
disjoint(+Set1, +Set2)
is true when the two given sets have no elements in common. It is the opposite of intersect/2. If either of the arguments is improper, disjoint/2 will fail.
is_set(+List)
is true when List is a proper list that contains no repeated elements.
pairfrom(?Set, ?Element1, ?Element2, ?Residue)
is true when Set is a list, Element1 occurs in list, Element2 occurs in list after Element1, and Residue is everything in Set bar the two Elements. The point of this thing is to select pairs of elements from a set without selecting the same pair twice in different orders.
intersect(+Set1, +Set2)
is true when the two sets have a member in common. It assumes that both sets are known, and that you don't care which element it is that they share.
subset(+Set1, +Set2)
is true when each member of Set1 occurs in Set2. It can only be used to test two given sets; it cannot be used to generate subsets. There is no predicate for generating subsets as such, but the predicates subseq/3, subseq0/2, subseq1/2 in library(lists) may do what you want (they preserve the order of elements within a list). Could be defined as:
          subset(Set1, Set2) :-
          	(   foreach(X,Set1),
          	    param(Set2)
          	do  memberchk(X,Set2)
          	).

set_order(+Xs, +Ys, -R)
is true when R is <, =, or > according as Xs is a subset of Ys, equivalent to Ys, or a superset of Ys.
seteq(+Set1, +Set2)
is true when each Set is a subset of the other.
list_to_set(+List, -Set)
is true when List and Set are lists, and Set has the same elements as List in the same order, except that it contains no duplicates. The two are thus equal considered as sets.
power_set(+Set, -PowerSet)
is true when Set is a list and PowerSet is a list of lists which represents the power set of the set that Set represents.
intersection(+Set1, +Set2, -Intersection)
is true when all three arguments are lists representing sets, and Intersection contains every element of Set1 which is also an element of Set2, the order of elements in Intersection being the same as in Set1. That is, Intersection represents the intersection of the sets represented by Set1 and Set2. Could be defined as:
          intersection(Set1, Set2, Intersection) :-
          	(   foreach(X,Set1),
          	    fromto(Intersection,S0,S,[]),
          	    param(Set2)
          	do  (member(X, Set2) -> S0 = [X|S] ; S0 = S)
          	).

intersection(+ListOfSets, -Intersection)
is true when Intersection is the intersection of all the sets in ListOfSets. The order of elements in Intersection is taken from the first set in ListOfSets. This has been turned inside out to minimise the storage turnover. Could be defined as:
          intersection([Set1|Sets], Intersection) :-
          	(   foreach(X,Set1),
          	    fromto(Intersection,S0,S,[]),
          	    param(Sets)
          	do  (   (   foreach(Set,Sets),
          		    param(X)
          		do  memberchk(X, Set)
          		) -> S0 = [X|S]
          	    ;   S0 = S
          	    )
          	).

subtract(+Set1, +Set2, -Difference)
is like intersect/3, but this time it is the elements of Set1 which are in Set2 that are deleted. Note that duplicated Elements of Set1 which are not in Set2 are retained in Difference. Could be defined as:
          subtract(Set1, Set2, Difference) :-
          	(   foreach(X,Set1),
          	    fromto(Difference,S0,S,[]),
          	    param(Set2)
          	do  (member(X, Set2) -> S0 = S ; S0 = [X|S])
          	).

symdiff(+Set1, +Set2, -Difference)
is true when Difference is the symmetric difference of Set1 and Set2, that is, if each element of Difference occurs in one of Set1 and Set2 but not both. The construction method is such that the answer will have no duplicates even if the Sets do.
setproduct(+Set1, +Set2, -CartesianProduct)
is true when Set1 is a set (list) and Set2 is a set (list) and CartesianProduct is a set of Elt1-Elt2 pairs, with a pair for for each element Elt1 of Set1 and Elt2 of Set2. Could be defined as:
          setproduct(Set1, Set2, Product) :-
          	(   foreach(H1,Set1),
          	    param(Set2),
          	    fromto(Product,P1,P3,[])
          	do  (   foreach(H2,Set2),
          		param(H1),
          		fromto(P1,[H1-H2|P2],P2,P3)
          	    do  true
          	    )
          	).

disjoint_union(+Set1, +Set2, -Union)
is true when disjoint(Set1, Set2) and union(Set1, Set2, Union), that is, Set1 and Set2 have no element in command and Union is their union. Could be defined as:
          disjoint_union(Set1, Set2, Union) :-
          	(   foreach(X,Set1),
          	    fromto(Union,[X|S],S,Set2),
          	    param(Set2)
          	do  nonmember(X, Set2)
          	).

union(+Set1, +Set2, -Union)
is true when subtract(Set1,Set2,Diff) and append(Diff,Set2,Union), that is, when Union is the elements of Set1 that do not occur in Set2, followed by all the elements of Set2. Could be defined as:
          union(Set1, Set2, Union) :-
          	(   foreach(X,Set1),
          	    fromto(Union,S0,S,Set2),
          	    param(Set2)
          	do  (member(X, Set2) -> S0 = S ; S0 = [X|S])
          	).

union(+Set1, +Set2, -Union, -Difference)
is true when union(Set1, Set2, Union) and subtract(Set1, Set2, Difference). Could be defined as:
          union(Set1, Set2, Union, Difference) :-
          	(   foreach(X,Set1),
          	    fromto(Union,S0,S,Set2),
          	    fromto(Difference,T0,T,[]),
          	    param(Set2)
          	do  (   member(X, Set2) -> S0 = S, T0 = T
          	    ;   S0 = [X|S], T0 = [X|T]
          	    )
          	).

union(+ListOfSets, -Union)
is true when Union is the union of all the sets in ListOfSets. It has been arranged with storage turnover in mind. Could be defined as:
          union(Sets, Union) :-
          	(   foreach(Set,Sets),
          	    param(Answer)
          	do  (   foreach(X,Set),
          		param(Answer)
          	    do  memberchk(X, Answer)
          	    )
          	),
          	append(Answer, [], Answer),	% cauterise it
          	!,
          	Union = Answer.

Send feedback on this subject.