
% take the union of two sets, 
%    assuming they are represented as lists

% the union of any set S with the empty set is S
union([], S, S).
union(S, [], S).

% if the front element of the first list is in the
%    second list then don't include it in the union 
%    (we'll pick it up when the first list is empty
%     and we incorporate the second list)
union([E|T], S2, S) :-
   member(E, S2), union(T, S2, S).

% since the front element of the first list is NOT
%    in the second list we include it in the union
union([E|T], S2, [E|S]) :-
   union(T, S2, S).

