next up previous index
Next: When to use Set Up: The Set Domain Library Previous: Constraint predicates   Index

Subsections

Examples

Set domains and interval reasoning

First we give a very simple example to demonstrate the expressiveness of set constraints and the propagation mechanism.

:- use_module(library(conjunto)).

[eclipse 2]: Car `:: {renault} .. {renault, bmw, mercedes, peugeot},
    Type_french = {renault, peugeot} , Choice `= Car /\ Type_french.

Choice = Choice{{renault} .. {peugeot, renault}}
Car = Car{{renault} .. {bmw, mercedes, peugeot, renault}}
Type_french = {peugeot, renault}

Delayed goals:
      inter_s({peugeot, renault}, Car{{renault}..{bmw, mercedes,
          peugeot, renault}}, Choice{{renault} .. {peugeot, renault}})
yes.
If now we add one cardinality constraint:
[eclipse 3]: Car `:: {renault} .. {renault, bmw, mercedes, peugeot},
    Type_french = {renault, peugeot} , Choice `= Car /\ Type_french,
    #(Choice, 2).

Car = Car{{peugeot, renault} .. {bmw, mercedes, peugeot, renault}}
Type_french = {peugeot, renault}
Choice = {peugeot, renault}
yes.
The first example gives a set of cars from which we know renault belongs to. The other labels /renault, bmw, mercedes, peugeot/ are possible elements of this set. The Type_french set is ground and Choice is the set term resulting from the intersection of the first two sets. The first execution tells us that renault is element of Choice and peugeot might be one. The intersection constraint is partially satisfied and might be reconsidered if one of the domain of the set terms involved changes. The cosntraint is delayed.

In the second example an additional constraint restricts the cardinality of Choice to 2. Satisfying this constraint implies setting the Choice set to {peugeot, renault}. The domain of this set has been modified so is the intersection constraint activated and solved again. The final result adds peugeot to the Car set variable. The intersection constraint is now satisfied and removed from the constraint store.

Subset-sum computation with convergent weight

A more elaborate example is a small decision problem. We are given a finite weighted set and a target t in N. We ask whether there is a subset s' of S whose weight is t. This also corresponds to having a single weighted set domain and to look for its value such that its weight is t.

This problem is NP-complete. It is approximated in Integer Programming using a procedure which "trims" a list according to a given parameter. For example, the set variable

S `:: {}..{e(a,104), e(b,102), e(c,201) ,e(d,101)}
is approximated by the set variable
S' `:: {}..{e(c,201) ,e(d, 101)}
if the parameter delta is 0.04 (0.04 = 02/n where n =# S)
:- use_module(library(conjunto)).

% Find the optimal solution to the subset-sum problem
solve(S1, Sum) :-
        getset(S),
        S1 `:: {}.. S,
        trim(S, S1),
        constrain_weight(S1, Sum),
        sum_weight(S1, W),
        Cost = Sum - W,
        min_max(labeling(S1), Cost).

% The set weight has to be less than Sum
constrain_weight(S1, Sum) :-
        sum_weight(S1, W),
        W #<= Sum.

% Get rid of a set of elements of the set according to a given delta
trim(S, S1) :-
        set2list(S, LS),
        trim1(LS, S1).
        
trim1(LS, S1) :-
        sort(2, =<, LS, [E | LSorted]), 
        getdelta(D),
        testsubsumed(D, E, LSorted, S1).

testsubsumed(_, _, [], _).
testsubsumed(D, E, [F | LS], S1) :-
        el_weight(E, We),
        el_weight(F, Wf),
        ( We =< (1 - D) * Wf ->
            testsubsumed(D, F, LS, S1)
        ;
            F notin S1,
            testsubsumed(D, E, LS, S1)
        ).

% Instantiation procedure
labeling(Sub) :-
        set(Sub),!.
labeling(Sub) :-
        max_weight(Sub, X),
        ( X in Sub ; X notin Sub ),
        labeling(Sub).

% Some sample data
getset(S) :- S = {e(a,104), e(b,102), e(c,201), e(d,101), e(e,305),
                e(f,50), e(g,70),e(h,102)}.
getdelta(0.05).

The approach is is the following: first create the set domain variable(s), here there is only one which is the set we want to find. We state constraints which limit the weight of the set. We apply the ``trim'' heuristics which removes possible elements of the set domain. And finally we define the cost term as a finite domain used in the min_max/2 predicate. The cost term is an integer. The conjunto.pl library makes sure that any modification of an fd term involved with a set term is propagated on the set domain. The labeling procedure refines a set domain by selecting the element of the set domain which has the biggest weight using max_weight(Sub, X), and by adding it to the lower bound of the set domain. When running the example, we get the following result:

[eclipse 3]: solve(S, 550).
Found a solution with cost 44
Found a solution with cost 24

S = {e(d, 101), e(e, 305), e(f, 50), e(g, 70)}
yes.
An interesting point is that in set based problems, the optimization criteria mainly concern the cardinality or the weight of a set term. So in practice we just need to label the set term while applying the fd optimization predicates upon the set cardinality or the set weight. There is no need to define additional optimization predicates.

The ternary Steiner system of order n

A ternary Steiner system of order n is a set of n * (n-1)\6 triplets of distinct elements taking their values between 1 and n, such that all the pairs included in two different triplets are different.

This problem is very well dedicated to be solved using set constraints: (i) no order is required in the triplet elements and (ii) the constraint of the problem can be easily written with set constraints saying that any intersection of two set terms contains at most one element. With a finite domain approach, the list of domain variables which should be distinct requires to be given explicitely, thus the problem modelling is would be bit ad-hoc and not valid for any n.

:- use_module(library(conjunto)).

% Gives one solution to the ternary steiner problem.
% n has to be congruent to 1 or 3 modulo 6.

steiner(N, LS) :-
        make_nbsets(N,NB),
        make_domain(N, Domain),
        init_sets(NB, Domain, LS),
        card_all(LS, 3),
        labeling(LS, []).

labeling([], _).
labeling([S | LS], L) :-
        refine(S),
        (LS = []  ; LS = [L2 | _Rest],
        all_distincts([S | L], L2),
        labeling(LS, [S | L])).

% the labeled sets are distinct from the set to be labeled
% this constraint is a disjonction so it is useless to put it
% before the labeling as no information would be deduced anyway
all_distincts([], _).
all_distincts([S1 |L], L2) :-
        distinctsfrom(S1, L2),
        all_distincts(L, L2).

distinctsfrom(S, S1) :-
        #(S /\ S1,C),
        fd:(C #<= 1).

% creates the required number of set variables according to n
make_nbsets(N,NB) :-
        NB is N * (N-1) // 6.

% initializes the domain of the variables according to n
make_domain(N, Domain) :-
        D :: 1.. N,
        dom(D, L),
        list2set(L, Domain).

init_sets(0, _Domain, []) :- !.
init_sets(NB, Domain, Sol) :-
        NB1 is NB-1,
        init_sets(NB1, Domain, Sol1),
        S `:: {} .. Domain,
        Sol = [S | Sol1].

% constrains the cardinality of each set variable to be equal to V (=3)
card_all([], _V).
card_all([Set1|LSets], V) :-
        #(Set1, V),
        card_all(LSets, V).

The approach with sets is the following: first we create the number of set variables required according to the initial problem definition such that each set variable is a triplet. Then to initialize the domain of these set variables we use the fd predicates which allow to define a domain by an implicit enumeration approach 1..n. This process is cleaner than enumerating a list of integer between 1 and n. Once all the domain variables are created, we constrain their cardinality to be equal to three. Then starts the labeling procedure where all the sets are labeled one after the other. Each time one set is labeled, constraints are stated between the labeled set and the next one to be labeled. This constraint states that two sets have at most one element in common. The semantics of '#(S intersect S1, C), C <= 1 is equivalent to a disjunction between set values. This implies that in the contraint propagation phase, no information can be deduced until one of the set is ground and some element has been added to the second one. No additional heuristics or tricks have been added to this simple example so it works well for n = 7, 9 but with the value 13 it becomes quite long. When running the example, we get the following result:

[eclipse 4]: steiner(7, S).
6 backtracks
0.75
S = [{1, 2, 3}, {1, 4, 5}, {1, 6, 7}, {2, 4, 6}, {2, 5, 7}, {3, 4, 7}, {3, 5, 6}]   
yes.


next up previous index
Next: When to use Set Up: The Set Domain Library Previous: Constraint predicates   Index
Warwick Harvey
2004-08-07