Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

CLP-FD suggestions

11 views
Skip to first unread message

marco

unread,
Dec 9, 2009, 8:20:12 AM12/9/09
to
I would like to solve a simple problem in CLP: assign 26 groups of
people of various sizes to 6 slots respecting the capacity of each
slot and minimizing the conflicts among the preferences of people.
Preferences are expressed, for each group, as a list of distances from
optimum.
With the following ILOG OPL program, it takes just few seconds:

int T = ...;
int G = ...;

int InPref[1..T][1..G] = ...;
int InCapac[1..T] = ...;
int InGroups[1..G] = ...;

dvar int Slots[1..T][1..G] in 0..1;

minimize
sum(t in 1..T)
sum(g in 1..G)
InPref[t][g] * Slots[t][g];

subject to {
forall(t in 1..T)
sum(g in 1..G) InGroups[g] * Slots[t][g] <= InCapac[t];

forall(g in 1..G)
sum(t in 1..T) Slots[t][g] == 1;
}

With (B-)Prolog it is very slow (my code follows). Have you a hint to
speed-up calculations? What is the name of this problem in CLP or OR
Literature? Thank you.

:- use_module(library(clpfd)).

:- include(cal3_data). % data, see below for a small example

collect([], _N, []).
collect([T|C], N, [T1|C1]) :-
element(N, T, T1),
collect(C, N, C1).

unique(N, N2, T) :-
N =< N2,
collect(T, N, L),
sum(L, #=, 1),
N1 is N + 1,
unique(N1, N2, T).
unique(_N, _N1, _T).

capac(_G, [], []).
capac(G, [T|C1], [C|C2]) :-
scalar_product(G, T, #=<, C),
capac(G, C1, C2).

minim(Groups, T, C, G, P) :-
flatten(T, T1),
T1 in 0..1,
% every group in a single slot
unique(1, Groups, T), !,
% the sum of the groups members in a slot cannot be greater than its
capacity
capac(G, T, C), !,
% minimize using preferences
scalar_product(P, T1, #=, Cost),
labeling([min(Cost)], T1),
format('Cost = ~w~n', [Cost]).

generate_res_list1(0, []).
generate_res_list1(M, [_L|C]) :-
M1 is M - 1,
generate_res_list1(M1, C).

generate_res_list(0, _, []).
generate_res_list(N, M, [L|C]) :-
generate_res_list1(M, L),
N1 is N - 1,
generate_res_list(N1, M, C).

% simple data example
data1(3, 2, Prefs, Capac, Compon) :-
Prefs = [[0, 1, 1], [1, 0, 0]], % slot 1 is the first choice for
group 1, a second choice for groups 2 and 3
Capac = [8, 6], % the first slot can receive 8 people, the second 6
Compon = [5, 3, 4]. % the first group has 5 people, the second 3, the
third 4

solve(T) :-
data1(Groups, Slots, Prefs, Capac, Compon),
flatten(Prefs, Prefs1),
generate_res_list(Slots, Groups, T),
minim(Groups, T, Capac, Compon, Prefs1).

Mats Carlsson

unread,
Dec 9, 2009, 9:44:27 AM12/9/09
to
On Dec 9, 2:20 pm, marco <marco.fa...@gmail.com> wrote:
> I would like to solve a simple problem in CLP: assign 26 groups of
> people of various sizes to 6 slots respecting the capacity of each
> slot and minimizing the conflicts among the preferences of people.
> Preferences are expressed, for each group, as a list of distances from
> optimum.

What is the data for this instance (26 groups, 6 slots)?

marco

unread,
Dec 9, 2009, 2:10:58 PM12/9/09
to

This is an example and its solution:

% cal3_data.pl
dati(Groups, Slots, Prefs, Capac, Compon) :-
Gruppi = 26,
Turni = 6,
Prefs = [
[1, 2, 6, 5, 6, 6, 3, 4, 4, 1, 2, 4, 4, 3, 1, 5, 1, 4, 5, 6, 5, 2,
5, 5, 3, 2],
[2, 3, 3, 2, 1, 4, 4, 2, 2, 6, 3, 1, 5, 5, 5, 6, 4, 2, 6, 4, 4, 5,
6, 2, 2, 1],
[5, 1, 1, 6, 3, 5, 5, 3, 6, 5, 5, 3, 6, 2, 4, 1, 6, 3, 2, 5, 1, 1,
2, 6, 4, 3],
[3, 6, 5, 3, 5, 3, 2, 1, 3, 3, 4, 2, 1, 1, 6, 2, 3, 5, 1, 3, 6, 3,
4, 3, 6, 5],
[4, 4, 4, 4, 2, 2, 1, 6, 1, 4, 6, 5, 2, 4, 2, 3, 5, 6, 4, 2, 3, 6,
1, 1, 1, 6],
[6, 5, 2, 1, 4, 1, 6, 5, 5, 2, 1, 6, 3, 6, 3, 4, 2, 1, 3, 1, 2, 4,
3, 4, 5, 4]
],
Capac = [18, 18, 18, 18, 18, 18],
Compon = [5, 4, 4, 4, 3, 3, 3, 3, 3, 4, 4, 5, 5, 2, 5, 3, 4, 4, 3, 3,
3, 5, 2, 4, 4, 5].

A solution:

T = [ [1, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 1, 0, 1, 0, 0, 0, 0,
0, 0, 0, 0, 0],
[0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
0, 0, 1],
[0, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 1, 0,
0, 0, 0],
[0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 1, 1, 0, 1, 0, 0, 1, 0, 0, 0, 0,
0, 0, 0],
[0, 0, 0, 0, 0, 0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1,
1, 1, 0],
[0, 0, 0, 1, 0, 1, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 1, 0, 1, 0, 0, 0,
0, 0, 0] ]

with Cost = 1

Joachim Schimpf

unread,
Dec 10, 2009, 12:48:30 AM12/10/09
to
marco wrote:
> I would like to solve a simple problem in CLP: assign 26 groups of
> people of various sizes to 6 slots respecting the capacity of each
> slot and minimizing the conflicts among the preferences of people.
> Preferences are expressed, for each group, as a list of distances from
> optimum.
> With the following ILOG OPL program, it takes just few seconds:

This model is much more amenable to an Integer Programming Solver
(although I'm not sure what solver OPL will use in your setup).

The following solution uses ECLiPSe with its interface to COIN-OR
and solves in about 20ms.

:- lib(eplex).
solve(Cost, Slots) :-
dati(NGroups, NSlots, Pref, Cap, Size),
model(NGroups, NSlots, Pref, Cap, Size, Slots, Obj),
optimize(min(Obj), Cost),
( foreacharg(Slot,Slots) do writeln(Slot) ).

model(NGroups, NSlots, Pref, Cap, Size, Slots, Obj) :-
dim(Slots, [NSlots,NGroups]),
Slots[1..NSlots,1..NGroups] $:: 0.0..1.0,
integers(Slots[1..NSlots,1..NGroups]),

( for(T,1,NSlots), param(Slots,Cap,Size,NGroups) do
( for(G,1,NGroups), foreach(U,Used), param(Slots,Size,T) do
U = Size[G] * Slots[T,G]
),
sum(Used) $=< Cap[T]
),

( for(G,1,NGroups), param(Slots,NSlots) do
sum(Slots[1..NSlots,G]) $= 1
),

( multifor([T,G],1,[NSlots,NGroups]), foreach(C,Cs), param(Pref,Slots) do
C = Pref[T,G] * Slots[T,G]
),
Obj = sum(Cs).


Note that in ECLiPSe you can use the same model/7 with the library(ic)
interval solver if you want to try a more "CLP-style" solution. Just
replace the solve-predicate as follows and recompile:

:- lib(ic).
:- lib(branch_and_bound).
solve(Cost, Slots) :-
dati(NGroups, NSlots, Pref, Cap, Size),
model(NGroups, NSlots, Pref, Cap, Size, Slots, Obj),
Cost #= eval(Obj),
minimize(search(Slots,0,input_order,indomain_max,complete,[]), Cost),
( foreacharg(Slot,Slots) do writeln(Slot) ).

This finds bad solutions quickly, but takes a long time to improve,
which I think is what you observed yourself. The ways to speed up
this CLP-style solution would be to introduce

- specialised global constraint(s)
- search heuristics, like assigning the preferred slots first

Cheers,
-- Joachim


% The data again - slightly modifed to use arrays instead of lists!

% simple data example
data1(3, 2, Prefs, Capac, Compon) :-

Prefs = []([](0, 1, 1), [](1, 0, 0)), % slot 1 is the first choice for group 1, a second choice

for groups 2 and 3

Capac = [](8, 6), % the first slot can receive 8 people, the second 6
Compon = [](5, 3, 4). % the first group has 5 people, the second 3, the third 4

% cal3_data.pl
dati(Gruppi, Turni, Prefs, Capac, Compon) :-


Gruppi = 26,
Turni = 6,

Prefs = [](
[](1, 2, 6, 5, 6, 6, 3, 4, 4, 1, 2, 4, 4, 3, 1, 5, 1, 4, 5, 6, 5, 2, 5, 5, 3, 2),
[](2, 3, 3, 2, 1, 4, 4, 2, 2, 6, 3, 1, 5, 5, 5, 6, 4, 2, 6, 4, 4, 5, 6, 2, 2, 1),
[](5, 1, 1, 6, 3, 5, 5, 3, 6, 5, 5, 3, 6, 2, 4, 1, 6, 3, 2, 5, 1, 1, 2, 6, 4, 3),
[](3, 6, 5, 3, 5, 3, 2, 1, 3, 3, 4, 2, 1, 1, 6, 2, 3, 5, 1, 3, 6, 3, 4, 3, 6, 5),
[](4, 4, 4, 4, 2, 2, 1, 6, 1, 4, 6, 5, 2, 4, 2, 3, 5, 6, 4, 2, 3, 6, 1, 1, 1, 6),
[](6, 5, 2, 1, 4, 1, 6, 5, 5, 2, 1, 6, 3, 6, 3, 4, 2, 1, 3, 1, 2, 4, 3, 4, 5, 4)
),
Capac = [](18, 18, 18, 18, 18, 18),
Compon = [](5, 4, 4, 4, 3, 3, 3, 3, 3, 4, 4, 5, 5, 2, 5, 3, 4, 4, 3, 3, 3, 5, 2, 4, 4, 5).

Marco Falda

unread,
Dec 10, 2009, 4:47:14 AM12/10/09
to
On 10 Dic, 06:48, Joachim Schimpf <jschi...@users.sourceforge.net>
wrote:

Thank you very much, I will try with ECLiPSe. In ILOG both approaches
are fast (the implicit CPLEX and the CP solver activated with the
directive "using CP;"), unfortunately it is not a free tool like
ECLiPSe.
Best regards. Marco

Joachim Schimpf

unread,
Dec 10, 2009, 8:20:45 AM12/10/09
to
Marco Falda wrote:
> Thank you very much, I will try with ECLiPSe. In ILOG both approaches
> are fast (the implicit CPLEX and the CP solver activated with the
> directive "using CP;"), unfortunately it is not a free tool like
> ECLiPSe.

I've put up 3 solutions on the ECLiPSe examples page
http://eclipse-clp.org/examples, see the first entry in the
"Planning and Scheduling" section.

One is the finite-domain solution with a preference-guided
search heuristic: this finds an optimum quickly, but has
trouble proving the optimality.

The other interesting variant is a hybrid LP/CP solution,
where a the finite domain solver is supported by an LP solver
solving a continuous relaxation, thus providing a lower cost
bound plus labeling heuristic. This is almost as fast as
the pure IP solution, but more flexible because you could add
further constraints that only an CP solver can handle.

Cheers,
Joachim

Mats Carlsson

unread,
Dec 10, 2009, 11:55:58 AM12/10/09
to
On Dec 10, 6:48 am, Joachim Schimpf <jschi...@users.sourceforge.net>
wrote:

> marco wrote:
> > I would like to solve a simple problem in CLP: assign 26 groups of
> > people of various sizes to 6 slots respecting the capacity of each
> > slot and minimizing the conflicts among the preferences of people.
> > Preferences are expressed, for each group, as a list of distances from
> > optimum.
> > With the following ILOG OPL program, it takes just few seconds:
>
> This model is much more amenable to an Integer Programming Solver
> (although I'm not sure what solver OPL will use in your setup).
>
> The following solution uses ECLiPSe with its interface to COIN-OR
> and solves in about 20ms.

The following simple CP model in SICStus Prolog finds the optimal
solution in 10ms:

:- use_module(library(lists)).
:- use_module(library(clpfd)).

solve(Slots, Cost) :-
statistics(runtime, _),
data(Ns, M, Prefs, Capac, Compon),
length(Slots, Ns),
( for(V,1,M),
foreach(C,Capac),
foreach(V-N,Values),
param(Slots,Compon)
do ( foreach(S1,Slots),
foreach(B1,Bs),
param(V)
do S1 #= V #<=> B1
),
sum(Bs, #=, N),
scalar_product(Compon, Bs, #=<, C)
),
transpose(Prefs, Matrix),
global_cardinality(Slots, Values, [cost(Cost,Matrix)]),
labeling([enum], [Cost|Slots]),
statistics(runtime, [_,T2]),
print_message(informational, format('~d ms',[T2])).

| ?- solve(Slots,Cost).
% 10 ms
Cost = 27,
Slots = [1,3,3,6,2,6,5,4,5,1|...] ? <0
Cost = 27,
Slots = [1,3,3,6,2,6,5,4,5,1,6,2,4,4,1,4,1,6,4,6,3,3,5,5,5,2] ?
yes

Cost = 27 instead of 1, for there are 26 groups and costs are 1-based.

The name of the game here is to have a good implementation of the
"global cardinality with costs" constraint:

http://www.emn.fr/x-info/sdemasse/gccat/Cglobal_cardinality_with_costs.html

--Mats

Marco Falda

unread,
Dec 10, 2009, 3:06:56 PM12/10/09
to
>  http://www.emn.fr/x-info/sdemasse/gccat/Cglobal_cardinality_with_cost...
>
> --Mats

Thank you very much also for this version, which is nearer to that I
wished to have obtained (the syntactic sugar for the loops is indeed
very useful, as I see in both codes)!
I have tried, by now, the ECLiPSe code; now I am curious to try also
this one, and to use the MiniZinc language to model it at a higher
level.
Best regards.


Marco


P.S.: I am sorry for my misleading cost associated with the data I
posted: it is 27 (cost = 1 referred to the zero based preferences,
which are more intuitive).

afa

unread,
Dec 10, 2009, 5:35:12 PM12/10/09
to
On Dec 9, 8:20 am, marco <marco.fa...@gmail.com> wrote:

This is a typical assignment problem. Here is a program written in B-
Prolog version 7.4:

go:-
data(NGroups, NSlots, Prefs, Capac, Compon),
length(Groups,NGroups), % use a variable for each group
Groups :: 1..NSlots,
% the capacity of each slot cannot be exceeded
foreach(I in 1..NSlots,
sum([(Groups[J]#=I)*Compon[J] : J in 1..NGroups]) #=< Capac[I]),
% compute cost from preferences
Cost #= sum([(Groups[J]#=I)*Prefs[I,J] : I in 1..NSlots, J in
1..NGroups]),
minof(labeling_ff(Groups),Cost,writeln((Groups,Cost))),
writeln(sol(Groups,Cost)).

data1(3, 2, Prefs, Capac, Compon) :-
Prefs = [[0, 1, 1], [1, 0, 0]],

Capac = [8, 6],

Compon = [5, 3, 4].

Unlike you original program, it does not model the problem as a
Boolean CSP. It uses foreach and list comprehension provided in
version 7.4. Array notations can be used to access list elements. So
for example, if L is list, L[I] means the Ith element of L. These new
constructs were inspired by logical loops in ECLiPSe, but are arguably
much simpler. You can find more examples of foreach and list
comprehension at:

http://probp.com/examples/index.html#FOREACH

Cheers,
Neng-Fa

Marco Falda

unread,
Dec 11, 2009, 4:24:32 AM12/11/09
to

I was using version 7.3 of B-Prolog, I will download the 7.4; thank
you for your advice.

My research interest is Fuzzy Temporal Reasoning and I would use CHRs
as a rapid prototyping tool; is the compiled library at "http://
probp.com/chr/" correct for the current version? (it seems to me that
the binary is no more compatible with the new version(s)). Thank you
again.

Marco

afa

unread,
Dec 11, 2009, 2:05:11 PM12/11/09
to
On Dec 11, 4:24 am, Marco Falda <marco.fa...@gmail.com> wrote:
> On 10 Dic, 23:35, afa <neng.z...@gmail.com> wrote:
>

> > On Dec 9, 8:20 am, marco <marco.fa...@gmail.com> wrote:

The original program I posted doesn't scale up well. B-Prolog now does
not have the global_cardinality constraint as provided by SICStus. The
following solution adopts the trick used in the ECLiPSe solution,
namely, doing labeling based on preferences. It quickly finds an
answer with cost 27 but it takes a long time to prove the optimality.

go:-
data(NGroups, NSlots, Prefs, Capac, Compon),

% use a variable for each group which takes on a slot
length(Groups,NGroups),
Groups :: 1..NSlots,

% the capacity cannot be exceeded
foreach(T in 1..NSlots,
sum([(Groups[G]#=T)*Compon[G] : G in 1..NGroups]) #=< Capac[T]),

% get cost from preferences
Cost #= sum([(Groups[G]#=T)*Prefs[T,G] : T in 1..NSlots, G in
1..NGroups]),

% OPrefs=[OPref1,OPref2,...] where each OPrefi is a sorted list
% [P1-T1,P2-T2,...], where Pi the preference for slot Ti
length(OPrefs,NGroups),
foreach(G in 1..NGroups,[Temp1,Temp2], % Temp1 and Temp2 are
local vars
(Temp1 @= [P-T : T in 1..NSlots,[P],P is Prefs[T,G]],
sort(Temp1,Temp2),
OPrefs[G] @= Temp2)),

minof(mylabeling(Groups,OPrefs),Cost,writeln((Groups,Cost))).

mylabeling([],_).
mylabeling([Group|Vars],[OPref|OPrefs]):-
member(_-Group,OPref),
mylabeling(Vars,OPrefs).

I am still playing with list comprehensions. Currently, a list
comprehension is interpreted as so only in calls to @=/2 and in sum,
min, and max constraint expressions, and an array notation is
interpreted as so only in calls to @=/2, arithmetic expressions, and
arithmetic constraints. In any other context, a list comprehension is
just interpreted as it is and an array notation such as A[I,J] is
interpreted as the term A^[I,J]. That is why you see [P-T : T in
1..NSlots,[P],P is Prefs[T,G]] (P is a local var) but not [Prefs[T,G]-
T : T in 1..NSlots].

One big difference between foreach in B-Prolog and loop constructs in
ECLiPSe and SICStus (I was surpprised to see that SICStus adopted
ECLiPSe's unpopular loop constructs! Sorry for being politically
incorrect:-) is that in foreach variables are assumed to be global
unless declared local (in ECLiPSe's loops, global variables need to be
declared using param).

> My research interest is Fuzzy Temporal Reasoning and I would use CHRs
> as a rapid prototyping tool; is the compiled library at "http://
> probp.com/chr/" correct for the current version? (it seems to me that
> the binary is no more compatible with the new version(s)). Thank you
> again.

I have uploaded leuven_chr.out. It should work with version 7.3 and
7.4. The CHR I have is old. You should contact Tom Schrijvers to see
if any newer version is available. Personally, I have never had a need
to use CHR. For most cases, action rules work just fine.

Cheers,
Neng-Fa

Markus Triska

unread,
Dec 12, 2009, 5:12:48 PM12/12/09
to
Mats Carlsson <ma...@sics.se> writes:

> The following simple CP model in SICStus Prolog finds the optimal
> solution in 10ms:

Very nice! I used the following formulation with latest git SWI Prolog:

:- use_module(library(clpfd)).

solve(Slots, Cost) :-
data(Ns, M, Prefs, Capacities, Members),
length(Slots, Ns),
numlist(1, M, Vs),
maplist(slots(Slots,Members), Vs, Capacities, Values),
transpose(Prefs, Matrix),
global_cardinality(Slots, Values, [cost(Cost,Matrix)]).

slots(Slots, Members, Slot, C, Slot-N) :-
maplist(eq_b(Slot), Slots, Bs),
sum(Bs, #=, N),
scalar_product(Members, Bs, #=<, C).

eq_b(S, E, B) :- S #= E #<==> B.

I obtained the same solution as you in less than 3 seconds:

%?- time((solve(Slots, Cost), labeling([step], [Cost|Slots]))).
%@ % 10,467,307 inferences, 2.070 CPU in 2.164 seconds (...)
%@ [1,3,3,6,2,6,5,4,5,1,6,2,4,4,1,4,1,6,4,6,3,3,5,5,5,2]
%@ Slots = [1, 3, 3, 6, 2, 6, 5, 4, 5|...],
%@ Cost = 27.

--
comp.lang.prolog FAQ: http://www.logic.at/prolog/faq/

Markus Triska

unread,
Dec 12, 2009, 6:17:31 PM12/12/09
to

> I obtained the same solution as you in less than 3 seconds:
>
> %?- time((solve(Slots, Cost), labeling([step], [Cost|Slots]))).
> %@ % 10,467,307 inferences, 2.070 CPU in 2.164 seconds (...)

I now noticed that you used the faster enum option, not step:

%?- time((solve(Slots, Cost), labeling([enum], [Cost|Slots]))).
%@ % 4,100,767 inferences, 0.830 CPU in 0.903 seconds (...)

Markus Triska

unread,
Dec 13, 2009, 3:05:38 PM12/13/09
to
afa <neng...@gmail.com> writes:

> B-Prolog now does not have the global_cardinality constraint

However, it has reified constraints and element/3, which at least in SWI
suffice to find a solution and prove its optimality with the following
formulation that you can no doubt easily adapt to B-Prolog:

:- use_module(library(clpfd)).

solve(Slots, Cost) :-
data(Ns, M, Prefs, Capacities, Members),
length(Slots, Ns),
numlist(1, M, Vs),
maplist(slots(Slots,Members), Vs, Capacities, Values),
transpose(Prefs, Matrix),

maplist(preferences(Vs), Slots, Matrix, Costs),
sum(Costs, #=, Cost),
maplist(cardinality(Slots), Values).

cardinality(Vs, Key-Val) :-
maplist(eq_b(Key), Vs, Bs),
sum(Bs, #=, Val).

preferences(Vs, Slot, Row, Cost) :-
element(N, Vs, Slot),
element(N, Row, Cost).

slots(Slots, Members, Slot, C, Slot-N) :-
maplist(eq_b(Slot), Slots, Bs),
sum(Bs, #=, N),
scalar_product(Members, Bs, #=<, C).

eq_b(X, Y, B) :- X #= Y #<==> B.

Example:

%?- time((solve(Slots, Cost), label([Cost|Slots]))).
%@ % 781,457 inferences, 0.160 CPU in 0.166 seconds (96% CPU, 4884106 Lips)


%@ Slots = [1, 3, 3, 6, 2, 6, 5, 4, 5|...],
%@ Cost = 27.

--
comp.lang.prolog FAQ: http://www.logic.at/prolog/faq/

afa

unread,
Dec 15, 2009, 8:48:48 PM12/15/09
to
On Dec 13, 3:05 pm, Markus Triska <tri...@logic.at> wrote:

It's a brilliant idea to use element/3, but if you use element/3 you
don't need to use global_cardinality. Actually, I couldn't figure out
how global_cardinality could help prune the search space. Below you
can find an encoding for B-Prolog. It gives a solution and proves its
optimality in a flash (less than 10ms in my slow PC).

You may need some explanations to understand the code. In the list
comprehension,

Costs @= [Cost : (Slot,Row) in (Groups,Matrix),
[I,Cost], % I and Cost are local
(element(I,Vs,Slot),element(I,Row,Cost))],

(Slot,Row) in (Groups,Matrix) iterates over two lists at the same
time. Also, int the definition for transpose/2, nested list
comprehensions are used. This turns out to be a very good example to
illustrate the uses of foreach and list comprehensions.

Cheers,
Neng-Fa

/* by Neng-Fa Zhou, Dec. 15, 2009, for B-Prolog 7.4 & up.
based on a solution written by Markus Triska for SWI-Prolog,
which was based a solution by Mats Carlsson for SICStus.
*/
go:-
time((solve(Groups,Cost),labeling([Cost|Groups]))),
writeln((Cost,Groups)).

solve(Groups,TotalCost) :-
data(NGroups,NSlots,Prefs,Capac,Compon),

% use a variable for each group which takes on a slot
length(Groups,NGroups),

% The capacity of each slot cannot be exceeded


foreach(T in 1..NSlots,
sum([(Groups[G]#=T)*Compon[G] : G in 1..NGroups]) #=< Capac
[T]),

% The same slot is used for each group in the
% capacity constraint and the cost function
transpose(Prefs,Matrix),
Vs @= [I : I in 1..NSlots],
Costs @= [Cost : (Slot,Row) in (Groups,Matrix),
[I,Cost], % I and Cost are local
(element(I,Vs,Slot),element(I,Row,Cost))],
sum(Costs) #= TotalCost.

transpose(Matrix,TMatrix):-
N is Matrix^length,
M is Matrix[1]^length,
TMatrix @= [Mji : J in 1..M,[Mji], % Mji is local
(Mji @= [Matrix[I,J] : I in 1..N])].

data(Groups,Slots,Prefs,Capac,Compon) :-
Groups = 26,
Slots = 6,
Prefs = [
[1,2,6,5,6,6,3,4,4,1,2,4,4,3,1,5,1,4,5,6,5,2,5,5,3,2],
[2,3,3,2,1,4,4,2,2,6,3,1,5,5,5,6,4,2,6,4,4,5,6,2,2,1],
[5,1,1,6,3,5,5,3,6,5,5,3,6,2,4,1,6,3,2,5,1,1,2,6,4,3],
[3,6,5,3,5,3,2,1,3,3,4,2,1,1,6,2,3,5,1,3,6,3,4,3,6,5],
[4,4,4,4,2,2,1,6,1,4,6,5,2,4,2,3,5,6,4,2,3,6,1,1,1,6],
[6,5,2,1,4,1,6,5,5,2,1,6,3,6,3,4,2,1,3,1,2,4,3,4,5,4]
],
Capac = [18,18,18,18,18,18],
Compon = [5,4,4,4,3,3,3,3,3,4,4,5,5,2,5,3,4,4,3,3,3,5,2,4,4,5].

Wit Jakuczun

unread,
Dec 16, 2009, 6:00:00 AM12/16/09
to
On 16 Gru, 02:48, afa <neng.z...@gmail.com> wrote:

> It's a brilliant idea to use element/3, but if you use element/3 you
> don't need to use global_cardinality. Actually, I couldn't figure out
> how global_cardinality could help prune the search space. Below you
> can find an encoding for B-Prolog. It gives a solution and proves its
> optimality in a flash (less than 10ms in my slow PC).
>

On my VERY slow PC :) I obtained following results (using SICStus):
1) version with element -> 13.9 ms


preferences(Vs, Slot, Row, Cost) :-

( foreach(V, Vs),
foreach(R, Row),
do true),
clpfd:element(N, Vs, Slot),
clpfd:element(N, Row, Cost).

2) version with table -> 14.8 ms


preferences(Vs, Slot, Row, Cost) :-

( foreach(V, Vs),
foreach(R, Row),
foreach([V, R], Tuples)
do true),
clpfd:table([[Slot,Cost]], Tuples).

3) version with global_cardinality (Matts version) -> 7.9 ms

This shows that on SICStus global_cardinality gives a significant
speed-up.

Execution time (average from 100 repetitions) was measured in C# with
much better resolution
comparing to statistics/2 Sicstus. Execution time includes prolog
beans overhead (small, but still).

Best regards,
Wit Jakuczun, WLOG Solutions

0 new messages