CLPFD max_member/2

Hi all,

Consider the code below,

schedule(T,EndTime) :- 
    Starts = [S1,S2],
    Ends = [E1,E2],
    T = [	task(S1,D1,E1,C1,t1),
			task(S2,D2,E2,C2,t2)
        ],
    [D1,D2] = [3, 2], 
    [C1,C2] = [1, 1],    
    Starts ins 8..12,
    Ends ins 8..12,  
    max_member(EndTime, Ends),   
    cumulative(T, [limit(2)]),
    labeling([min(EndTime)],Starts).

?- schedule(T,EndTime)
EndTime = 10,
T = [task(8,3,11,1,t1), task(8,2,10,1,t2)]

I simply do not understand why EndTime is not equal to 11.

Use max_list/2 instead - evidence:

?- X #> Y, max_list([X, Y], M).
X = M,
Y#=<M+ -1.

?- X #> Y, max_list([Y, X], M).
X = M,
Y#=<M+ -1.

The problem with max_member/2 is standard order of terms, which behaves badly with vars, e.g.:

?- compare(C, X, Y).
C = (<).
1 Like

Hi Brebs

Thank you for your answer.

  • max_list/2 is not a CLP(FD) predicate; it requires importing the lists library.
  • As far as I understand, max_member/2, like any CLP(FD) predicate, posts a constraint. I expected that after labeling, EndTime would hold the correct value. This seems like a bug to me (or I might be missing something). Is that what you mean when you say it “behaves badly”?

It doesn’t require importing anything, library(lists) is autoloaded.

The two predicates, max_list/2 and max_member/2 (and also max_member/3) are all sitting next to each other in the autoloaded library(lists). max_member/2 is not a CLP(FD) predicate, at least not in SWI-Prolog.

You can see the definition of max_member/2 and any other predicate by clicking the orange circle with the “:-” in it in the far right of the blue header line.

“Behaves badly” could indeed be considered sloppy language. I at least am not clever enough to grok how CLP(FD) constraints interact with the rest of the language and I am confounded too often.

Apologies, I was wrong, max_list/2 does not use clpfd either.

Can use this, taking inspiration from prolog - clpfd - constraint upper bond of domain the be the maximum of a list of elements - Stack Overflow

clpfd_max_list([H|T], M) :-
    foldl(clpfd_max, T, H, M).

clpfd_max(I, J, M) :-
    M #= max(I, J).

Example:

?- X #< Y, Y #> Z, clpfd_max_list([X, Y, Z], M).
_A#>=X,
X#=<Y+ -1,
_A#=max(Y, X),
_A#>=Y,
Z#=<Y+ -1,
M#>=Z,
M#=max(Z, _A),
M#>=_A.

This shows that clpfd has not quite concluded neatly that M must be Y… but it will :grinning:

For the standard order, see SWI-Prolog -- Standard Order of Terms - the good news is that we can write predicates using e.g. ground/1 and nonvar/1 to act as we choose.

Sorry, I was wrong I thought that max_member/2 was a clpfd predicate.
Replacing it with max_list/2 in my code results in an error (arguments are insufficiently instantiated), but your clpfd_max_list/2 works perfectly.

Thanks a lot.