next up previous index
Next: Set Domain output Up: The Set Domain Library Previous: User-defined constraints   Index

Example of defining a new constraint

The following example demonstrates how to create a new set constraint. To show that set inclusion is not restricted to ground herbrand terms we can take the following constraint which defines lattice inclusion over lattice domains:

S_1 incl S
Assuming that S and S1 are specific set variables of the form
S `:: {} ..{{a,b,c},{d,e,f}}, ..., S_1 `:: {} ..{{c},{d,f},{g,f}}
we would like to define such a predicate that will be woken as soon as one or both set variables' domains are updated in such a way that would require updating the other variable's domain by propagating the constraint. This constraint definition also shows that if one wants to iterate over a ground set (set of known elements) the transformation to a list is convenient. In fact iterations do not suit sets and benefit much more from a list structure. We define the predicate incl(S,S1) which corresponds to this constraint:

:- use_module(library(conjunto)).
incl(S,S1) :-
          set(S),set(S1),
          !,
          check_incl(S, S1).
incl(S, S1) :-
          set(S),
          set_range(S1, Glb1, Lub1),
          !,
          check_incl(S, Lub1),
          S + Glb1 `= S1NewGlb,
          modify_bound(glb, S1, S1NewGlb).
incl(S, S1) :-
          set(S1),
          set_range(S, Glb, Lub),
          !,
          check_incl(Glb, S1),
          large_inter(S1, Lub, SNewLub),
          modify_bound(lub, S, SNewLub).
incl(S,S1) :-
          set_range(S, Glb, Lub),
          set_range(S1, Glb1, Lub1),
          check_incl(Glb, Lub1),
          Glb \/ Glb1 `= S1NewGlb,
          large_inter(Lub, Lub1, SNewLub),
          modify_bound(glb, S1, S1NewGlb),
          modify_bound(lub, S, SNewLub),
          ( (set(S) ; set(S1)) ->
               true
         ;
               make_suspension(incl(S, S1),2, Susp),
               insert_suspension([S,S1], Susp, del_any of set, set)
          ),
          wake.

large_inter(Lub, Lub1, NewLub) :-
          set2list(Lub, Llub),
          set2list(Lub1, Llub1),
          largeinter(Llub, Llub1, LNewLub),
          list2set(LNewLub, NewLub).

largeinter([], _, []).
largeinter([S | List_set], Lub1, Snew) :-
          largeinter(List_set, Lub1, Snew1),
          ( contained(S, Lub1) ->
                Snew = [S | Snew1]
          ;
                Snew = Snew1
          ).

check_incl({}, _S) :-!.
check_incl(Glb, Lub1) :-
          set2list(Glb, Lsets),
          set2list(Lub1, Lsets1),
          all_union(Lsets, Union),
          all_union(Lsets1, Union1),
          Union `< Union1,!,
          checkincl(Lsets,Lsets1).
checkincl([], _Lsets1).
checkincl([S | Lsets],Lsets1):-
          contained(S, Lsets1),
          checkincl(Lsets,Lsets1).

contained(_S, []) :- fail,!.
contained(S, [Ss | Lsets1]) :-
          (S `< Ss ->
                true
          ;
                contained(S, Lsets1)
          ).

The execution of this constraint is dynamic, i.e., the predicate incl/2 is called and woken following the following steps:


next up previous index
Next: Set Domain output Up: The Set Domain Library Previous: User-defined constraints   Index
Warwick Harvey
2004-08-07