2.12 Set of answers

Prolog has two built-in predicates designed to collect together objects resulting from successful computations:

bagof(Things, Condition, Bag)
setof(Things, Condition, Bag)

For example, in section 2.5, the 'height' predicate was defined to be

height(Node,H) :- setof(Z,ht(Node,Z),Set),
                  max(Set,0,H).

The 'setof' computation gathers together all of the Zs that result from the 'ht(Node,Z)' computations and lists the distinct (different) Zs in Set. For example,

?- setof(Z,ht(a,Z,Set).
Set=[3,4,2,]

?- setof(Z,ht(a,Z),Set), max(Set,0,H).
Set=[3,4,2] H=4

where Set=[3,4,2] represents individual results of 'ht' computations of 'a' above its leaf descendants, but the height of 'a' is H=4. The reader will have to go back to section 2.5 for the definitions involving 'ht'. Compare this with:

?- bagof(Z,ht(a,Z),Bag).
Bag=[3,3,4,2,3,3,3,3,3,3]

Generally, 'bagof' computes a Bag of all possibilities with repeats, and 'setof' computes a Set of distinct results.

The standard 'bagof' predicate could be simulated as follows:

bag-of(X,Goal,Bag) :-   post_it(X,Goal),
                        gather([],Bag).

post_it(X,Goal) :- call(Goal),         /* try Goal */
                   asserta(data999(X)) /* assert above others */
                   fail.               /* force backtracking   */
post_it(_,_).                          /* gratuitous success    */

gather(B,Bag) :-  data999(X),          /* find next recorded solution  */
                  retract(data999(X)), /* erase posting       */
                  gather([X|B],Bag),   /* continue  ...        */
                  !.                   /* cut off rule below */
gather(S,S).                           /* when done          */

The reader should spend some time with these definitions. The 'bag-of' definition requires that first all of the answers be posted to memory using 'asserta'. Try various 'asserta(p(Constant))' goals, where 'Constant' has various constant values like 'a', 'b', etc., each followed respectively by a 'listing(p)' goal to see how Prolog asserts. See also the definitions of 'assert', 'asserta', 'assertz' and 'retract' in section 4.9. Secondly, 'bag-of' then gathers all of the posted values together into a list.

Exercise 2.12.1 Modify the 'bagof' simulation given in 'bag-of' above to create a simulation of Prolog's 'setof' called 'set-of'. Use 'assert' and 'retract' in similar ways but make sure that 'gather' only gathers unique Xs that have not been previously gathered.


Prolog Tutorial Contents