5

I have written a CSP program using CLP(FD) and SWI-Prolog.

I think I need to improve my constraints' writing when I use the mod operator together with #\/ in my predicates.

A short example :

:- use_module(library(clpfd)).

constr(X,Y,Z) :-
   X in {1,2,3,4,5,6,7},
   Y in {3,5,7},
   Z in {1,2},
   ((X #= 3)) #==> ((Y mod 3 #= 0) #\/ (Y mod 7 #= 0)),
   ((Z #= 1)) #<==> ((Y mod 3 #= 0) #\/ (Y mod 7 #= 0)).

If I call constr(3,Y,Z)., I get Z #= 1or Z #= 2. This is because some intermediate variables (relative to the mod expressions) still need to be evaluated.

Of course the ideal would be to only obtain Z #= 1.

How could this be done ?

I know that if I write instead

((X #= 3)) #==> ((Z #= 1)),
((Z #= 1)) #<==> ((Y mod 3 #= 0) #\/ (Y mod 7 #= 0)).

everything works as expected.

But is this reification mandatory ? I mean, do I have to create a reification variable each time I have this pattern in my constraints :

(A mod n1 #= 0) #\/ (B mod n2 #= 0) #\/ ... #\/ (Z mod n26 #= 0)

Thanks in advance for your ideas.

M.V.
  • 177
  • 9

3 Answers3

5

That's a very good observation and question! First, please note that this is in no way specific to mod/2. For example:

?- B #<==> X #= Y+Z, X #= Y+Z.
B in 0..1,
X#=_G1122#<==>B,
Y+Z#=X,
Y+Z#=_G1122.

In contrast, if we write this declaratively equivalently as:

?- B #<==> X #= A, A #= Y + Z, X #= A.

then we get exactly as expected:

A = X,
B = 1,
Y+Z#=X.

What is going on here? In all systems I am aware of, reification in general uses a decomposition of CLP(FD) expressions which unfortunately removes important information that is not recovered later. In the first example, it is not detected that the constraint X #= Y+Z is entailed, i.e., necessarily holds.

On the other hand, entailment of a single equality with non-composite arguments is correctly detected, as in the second example.

So yes, in general, you will need to rewrite your constraints in this way to enable optimal detection of entailment.

The lurking question is of course whether the CLP(FD) system could help you to detect such cases and perform the rewriting automatically. Also in this case, the answer is yes, at least for certain cases. However, the CLP(FD) system typically is told only individual constraints in a certain sequence, and recreating and analyzing a global overview of all posted constraints in order to merge or combine previously decomposed constraints is typically not worth the effort.

mat
  • 40,498
  • 3
  • 51
  • 78
  • Thanks a lot, @mat, for this deep explanation. How could I make the CLP(FD) system help me detect such cases and perform the rewriting automatically ? My idea was to write : `((X #= 3)) #==> T, ((Z #= 1)) #<==> T, T #<==> ((Y mod 3 #= 0) #\/ (Y mod 7 #= 0)).` – M.V. May 26 '16 at 08:16
  • 1
    It would be easy to add particular special cases to the CLP(FD) system, but this is not sufficient: For example, in your case we also would need to modify `(#=)/2` (which uses a similar decomposition for arithmetic expressions) to detect at runtime (or compile time) whether one of the special cases is now applicable, *and then* rewrite the constraints dynamically. I consider the overhead of this too high: It is better that you rewrite the expressions yourself in this way, which should be quite easy. You can open a new question to discuss how we can rewrite such expressions within your program! – mat May 26 '16 at 08:33
  • Ok, thanks again. I will try to make this rewriting by myself. – M.V. May 26 '16 at 09:04
3

With the (semi-official) contracting/1 predicate, you can minimize some domains in one fell swoop. In your case:

| ?- constr(3,Y,Z).
clpz:(Z#=1#<==>_A),
clpz:(_B#=0#<==>_C),
clpz:(_D#=0#<==>_E),
clpz:(_F#=0#<==>_G),
clpz:(_H#=0#<==>_I),
clpz:(_C#\/_E#<==>1),
clpz:(_G#\/_I#<==>_A),
clpz:(Y mod 3#=_B),
clpz:(Y mod 3#=_F),
clpz:(Y mod 7#=_D),
clpz:(Y mod 7#=_H),
clpz:(Y in 3\/5\/7),
clpz:(Z in 1..2),
clpz:(_C in 0..1),
clpz:(_B in 0..2),
clpz:(_E in 0..1),
clpz:(_D in 0..6),
clpz:(_A in 0..1),
clpz:(_G in 0..1),
clpz:(_F in 0..2),
clpz:(_I in 0..1),
clpz:(_H in 0..6) ? ;
no

And now by adding a single goal:

| ?- constr(3,Y,Z), clpz:contracting([Z]).
Z = 1,
clpz:(_A#=0#<==>_B),
clpz:(_C#=0#<==>_D),
clpz:(_E#=0#<==>_F),
clpz:(_G#=0#<==>_H),
clpz:(_B#\/_D#<==>1),
clpz:(_F#\/_H#<==>1),
clpz:(Y mod 3#=_A),
clpz:(Y mod 3#=_E),
clpz:(Y mod 7#=_C),
clpz:(Y mod 7#=_G),
clpz:(Y in 3\/5\/7),
clpz:(_B in 0..1),
clpz:(_A in 0..2),
clpz:(_D in 0..1),
clpz:(_C in 0..6),
clpz:(_F in 0..1),
clpz:(_E in 0..2),
clpz:(_H in 0..1),
clpz:(_G in 0..6) ? ;
no

In other words, a more consistent version of your predicate constr/3 would be:

constr_better(X, Y, Z) :-
   constr(X, Y, Z),
   clpz:contracting([Z]).

Above I used SICStus with library(clpz) which is the successor to library(clpfd) of SWI which has clpfd:contracting/1, too.

false
  • 10,264
  • 13
  • 101
  • 209
  • `constr/3` is your definition, verbatim, no extra improvements. And then I used the predefined `contracting/1`. – false Jan 11 '17 at 13:39
  • So do I have to right this : `res(X,L) :- contracting(X), setof(X, indomain(X), L).` ? – M.V. Jan 11 '17 at 13:41
  • Why do you want to use this `setof/3` at all? Seems you are interested in getting better bounds. And contracting/1 does this for you. – false Jan 11 '17 at 13:42
  • I get my resulting domains in "out" variables Xout, Yout, Zout. So my labelling predicates were : `res(X,L) :- setof(X, indomain(X), L). constrChoice(X,Y,Z,XOut,YOut,ZOut) :- constr(X,Y,Z), res(X,XOut),res(Y,YOut),res(Z,ZOut).` I just need to adapt this to add `contracting/1`, but where ? – M.V. Jan 11 '17 at 13:50
  • You add `contracting/1` like above! – false Jan 11 '17 at 14:10
  • `res(X,L) :- setof(X, indomain(X), L). constrChoice(X,Y,Z,XOut,YOut,ZOut) :- constr(X,Y,Z), clpfd:contracting([X]), clpfd:contracting([Y]), clpfd:contracting([Z]), res(X,XOut),res(Y,YOut),res(Z,ZOut).` seems to be working :) – M.V. Jan 11 '17 at 14:13
  • Or simpler `res(X,L) :- clpfd:contracting([X]), setof(X, indomain(X), L). constrChoice(X,Y,Z,XOut,YOut,ZOut) :- constr(X,Y,Z), res(X,XOut),res(Y,YOut),res(Z,ZOut).` – M.V. Jan 11 '17 at 14:14
  • Thanks a lot for your precious help. The use of `contracting/1` on all my variables (86) doesn't cost more time, a relief. – M.V. Jan 11 '17 at 14:37
  • I just noticed that the use of `contracting/1` does nothing when you have `#/\ ` instead of `#\/ ` : `constr(X,Y,Z) :- X in {1,2,3,4,5,6,7}, Y in {3,5,7}, Z in {1,2}, ((X #= 3)) #==> ((Y mod 3 #= 0) #/\ (Y mod 7 #= 0)), ((Z #= 1)) #<==> ((Y mod 3 #= 0) #/\ (Y mod 7 #= 0)).` Calling `constr(3,Y,Z), clpfd:contracting([Y,Z]).` gives `Z in 1..2.` – M.V. Jan 11 '17 at 16:12
  • You last definition fails for `constr(3,Y,Z)` - without any need for `contracting` – false Jan 11 '17 at 17:34
1

After trying many things, I ended up with these conclusions, tell me if I am wrong (sorry, I am a beginner).

Let's consider this sample :

:- use_module(library(clpfd)).

constr(X,Y,Z) :-
   X in {1,2,3,4,5,6,7},
   Y in {3,5,7,21,42},
   Z in {1,2},
   (X #= 3) #==> ((Y mod 3 #= 0) #\/ (Y mod 7 #= 0)),
   (Z #= 1) #<==> ((Y mod 3 #= 0) #\/ (Y mod 7 #= 0)).

constr_better(X,Y,Z) :- constr(X,Y,Z), clpfd:contracting([X,Y,Z]).

res(X,L) :- setof(X, indomain(X), L).

constrChoice(X,Y,Z,XOut,YOut,ZOut) :-
   constr(X,Y,Z),
   res(X,XOut),res(Y,YOut),res(Z,ZOut).

constrChoiceBetter(X,Y,Z,XOut,YOut,ZOut) :-
   constr_better(X,Y,Z),
   res(X,XOut),res(Y,YOut),res(Z,ZOut).
  1. constr(3,Y,Z) gives Z in 1..2 but constrChoice(3,Y,Z,Xout,Yout,Zout) gives Zout=[1] , so no need to use contracting/1 because the use of setof/3 together with indomain/1 does the job. No need to rewrite prolog predicates either.

  2. Now if I have AND #/\ instead of OR #\/, none of the calls constr(3,Y,Z),constrChoice(3,Y,Z,Xout,Yout,Zout) or constrChoiceBetter(3,Y,Z,Xout,Yout,Zout) gives that Z must be 1. I effectively have that Y is 21 or 42, but Z is told to be 1 or 2. What works : write that Y mod 21 #= 0 directly, and then no need to use contracting/1 either.

Thanks for your comments.

false
  • 10,264
  • 13
  • 101
  • 209
M.V.
  • 177
  • 9
  • Sorry about that... What is difficult to understand ? – M.V. Jan 12 '17 at 14:26
  • In 2 your are describing indirectly how the code looks like, but that is impossible to reproduce. – false Jan 12 '17 at 14:27
  • What is impossible to reproduce ? I don't see what you mean. In my code sample replace #\/ with #/\ then call the queries in 2, you will see that Z is not said to be 1. – M.V. Jan 12 '17 at 14:33
  • No idea how the *very precise* code looks like in 2. I already showed you that this fails! – false Jan 12 '17 at 14:47
  • You need to put minimal and complete examples out! – false Jan 12 '17 at 14:49
  • It's not the same example as above, I added 21 and 42 into Y's domain value, so it doesn't fail. You obtain X = 3, Y in 21 \/ 42, Z in 1..2 – M.V. Jan 12 '17 at 15:35