I have to meet 6 project students in pairs and I have 3 slots in which I can do this, but there are some constraints.
Let's call the students student1 etc and the slots slot1 etc. A higher-numbered slot occurs after a lower-numbered slot.
The constraints are:
I should meet each student exactly once.
I have written the following program to solve this scheduling puzzle:
student(student1).
student(student2).
student(student3).
student(student4).
student(student5).
student(student6).
slot(slot1).
slot(slot2).
slot(slot3).
constraint1(Slot1, _Slot2, _Slot3) :-
member(student1-_, Slot1).
constraint2(Slot1, Slot2, Slot3) :-
( member(student2-_, Slot1), member(student3-_, Slot1) );
( member(student2-_, Slot2), member(student3-_, Slot2) );
( member(student2-_, Slot3), member(student3-_, Slot3) ).
constraint3(Slot1, Slot2, Slot3) :-
\+ ( member(student1-_, Slot1), member(student4-_, Slot1) ),
\+ ( member(student1-_, Slot2), member(student4-_, Slot2) ),
\+ ( member(student1-_, Slot3), member(student4-_, Slot3) ).
constraint4(Slot1, _, Slot3) :-
\+ member(student6-_, Slot1),
\+ member(student6-_, Slot3).
meetings_one_two_three(Slot1, Slot2, Slot3) :-
% Generate all possible assignments of students to slots.
findall( (Slot1, Slot2, Slot3), (
% Slot 1
select_two_students(S1_1, S1_2, _Remaining1),
Slot1 = [S1_1-S1_2, S1_2-S1_1], % Assign to slot 1.
% Slot 2
select_two_students(S2_1, S2_2, _Remaining2),
Slot2 = [S2_1-S2_2, S2_2-S2_1], % Assign to slot 2.
% Slot 3
select_two_students(S3_1, S3_2, _Remaining3),
Slot3 = [S3_1-S3_2, S3_2-S3_1], % Assign to slot 3.
all_different([S1_1, S1_2, S2_1, S2_2, S3_1, S3_2]), % All students must be different.
constraint1(Slot1, Slot2, Slot3),
constraint2(Slot1, Slot2, Slot3),
constraint3(Slot1, Slot2, Slot3),
constraint4(Slot1, Slot2, Slot3)
), Solutions),
member( (Slot1, Slot2, Slot3), Solutions). % Select one solution.
select_two_students(S1, S2, Remaining) :-
student(S1),
student(S2),
S1 @< S2, % Ensure we do not generate (A, B) and (B, A) which is essential for efficiency. This condition reduces the search space.
findall(Other, (student(Other), Other \= S1, Other \= S2), Remaining).
all_different([]).
all_different([H|T]) :-
\+ member(H,T),
all_different(T).
When I consult and query the knowledge base and input the following at the Prolog prompt, I receive these results:
?- consult(scheduling).
true.
?- meetings_one_two_three(Slot1, Slot2, Slot3).
Slot1 = [student1-student5, student5-student1],
Slot2 = [student4-student6, student6-student4],
Slot3 = [student2-student3, student3-student2].
This is correct, but the S1 @< S2
should have prevented the generation of both student1-student5
and student5-student1
, for example.
I, then, realized that the problem must be the following three lines:
Slot1 = [S1_1-S1_2, S1_2-S1_1], % Assign to slot 1.
Slot2 = [S2_1-S2_2, S2_2-S2_1], % Assign to slot 2.
Slot3 = [S3_1-S3_2, S3_2-S3_1], % Assign to slot 3.
So, I modified them to the following:
Slot1 = [S1_1-S1_2], % Assign to slot 1.
Slot2 = [S2_1-S2_2], % Assign to slot 2.
Slot3 = [S3_1-S3_2], % Assign to slot 3.
I was confident this would fix the issue but unfortunately I get false.
What am I missing? Could someone please help me understand what I am doing wrong and how I can resolve it with minimal changes?
I have to meet 6 project students in pairs and I have 3 slots in which I can do this, but there are some constraints.
Let's call the students student1 etc and the slots slot1 etc. A higher-numbered slot occurs after a lower-numbered slot.
The constraints are:
I should meet each student exactly once.
I have written the following program to solve this scheduling puzzle:
student(student1).
student(student2).
student(student3).
student(student4).
student(student5).
student(student6).
slot(slot1).
slot(slot2).
slot(slot3).
constraint1(Slot1, _Slot2, _Slot3) :-
member(student1-_, Slot1).
constraint2(Slot1, Slot2, Slot3) :-
( member(student2-_, Slot1), member(student3-_, Slot1) );
( member(student2-_, Slot2), member(student3-_, Slot2) );
( member(student2-_, Slot3), member(student3-_, Slot3) ).
constraint3(Slot1, Slot2, Slot3) :-
\+ ( member(student1-_, Slot1), member(student4-_, Slot1) ),
\+ ( member(student1-_, Slot2), member(student4-_, Slot2) ),
\+ ( member(student1-_, Slot3), member(student4-_, Slot3) ).
constraint4(Slot1, _, Slot3) :-
\+ member(student6-_, Slot1),
\+ member(student6-_, Slot3).
meetings_one_two_three(Slot1, Slot2, Slot3) :-
% Generate all possible assignments of students to slots.
findall( (Slot1, Slot2, Slot3), (
% Slot 1
select_two_students(S1_1, S1_2, _Remaining1),
Slot1 = [S1_1-S1_2, S1_2-S1_1], % Assign to slot 1.
% Slot 2
select_two_students(S2_1, S2_2, _Remaining2),
Slot2 = [S2_1-S2_2, S2_2-S2_1], % Assign to slot 2.
% Slot 3
select_two_students(S3_1, S3_2, _Remaining3),
Slot3 = [S3_1-S3_2, S3_2-S3_1], % Assign to slot 3.
all_different([S1_1, S1_2, S2_1, S2_2, S3_1, S3_2]), % All students must be different.
constraint1(Slot1, Slot2, Slot3),
constraint2(Slot1, Slot2, Slot3),
constraint3(Slot1, Slot2, Slot3),
constraint4(Slot1, Slot2, Slot3)
), Solutions),
member( (Slot1, Slot2, Slot3), Solutions). % Select one solution.
select_two_students(S1, S2, Remaining) :-
student(S1),
student(S2),
S1 @< S2, % Ensure we do not generate (A, B) and (B, A) which is essential for efficiency. This condition reduces the search space.
findall(Other, (student(Other), Other \= S1, Other \= S2), Remaining).
all_different([]).
all_different([H|T]) :-
\+ member(H,T),
all_different(T).
When I consult and query the knowledge base and input the following at the Prolog prompt, I receive these results:
?- consult(scheduling).
true.
?- meetings_one_two_three(Slot1, Slot2, Slot3).
Slot1 = [student1-student5, student5-student1],
Slot2 = [student4-student6, student6-student4],
Slot3 = [student2-student3, student3-student2].
This is correct, but the S1 @< S2
should have prevented the generation of both student1-student5
and student5-student1
, for example.
I, then, realized that the problem must be the following three lines:
Slot1 = [S1_1-S1_2, S1_2-S1_1], % Assign to slot 1.
Slot2 = [S2_1-S2_2, S2_2-S2_1], % Assign to slot 2.
Slot3 = [S3_1-S3_2, S3_2-S3_1], % Assign to slot 3.
So, I modified them to the following:
Slot1 = [S1_1-S1_2], % Assign to slot 1.
Slot2 = [S2_1-S2_2], % Assign to slot 2.
Slot3 = [S3_1-S3_2], % Assign to slot 3.
I was confident this would fix the issue but unfortunately I get false.
What am I missing? Could someone please help me understand what I am doing wrong and how I can resolve it with minimal changes?
This can be solved using clpb.
:- use_module(library(clpb)).
solve(Vars) :-
Vars = [S11,S12,S13,S14,S15,S16, % Slot1 can meet among these 6 students
S21,S22,S23,S24,S25,S26, % Slot2 can meet among these 6 students
S31,S32,S33,S34,S35,S36],% Slot3 can meet among these 6 students
% Contraints
% A student can only be in one slot
sat(card([1],[S11, S21, S31])),
sat(card([1],[S12, S22, S32])),
sat(card([1],[S13, S23, S33])),
sat(card([1],[S14, S24, S34])),
sat(card([1],[S15, S25, S35])),
sat(card([1],[S16, S26, S36])),
% student1 must be in slot1
sat(S11),
% student2 and student3 must meet in the same slot.
sat(card([1],[S12*S13,S22*S23,S32*S33])),
% EDIT this clause can be removed since a student can only be in one slot
% sat(card([2],[S12,S13,S22,S23,S32,S33])),
% student1 and student4 cannot be in the same slot.
sat(card([0],[S11*S14])),
sat(card([0],[S21*S24])),
sat(card([0],[S31*S34])),
% student6 cannot be in slot1 or slot3.
sat(card([0],[S16,S36])),
% each slot must have 2 students
sat(card([2], [S11,S12,S13,S14,S15,S16])),
sat(card([2], [S21,S22,S23,S24,S25,S26])),
sat(card([2], [S31,S32,S33,S34,S35,S36])),
labeling(Vars),
forall(between(0,2,Sl), forall(between(0,5,St), affiche(Vars,Sl,St))).
affiche(V, Sl, St) :-
Z is 6*Sl+St,
nth0(Z,V,N),
( sat(N) -> Sl1 is Sl + 1, St1 is St + 1, writef('Slot %d student %d\n', [Sl1,St1]);true).
We get :
?- solve(V).
Slot 1 student 1
Slot 1 student 5
Slot 2 student 4
Slot 2 student 6
Slot 3 student 2
Slot 3 student 3
V = [1, 0, 0, 0, 1, 0, 0, 0, 0|...].
with plain old generate and test it's pretty simple:
meetings_one_two_three(Slot1, Slot2, Slot3) :-
Students = [student1,student2,student3,student4,student5,student6],
Slots = [Slot1,Slot2,Slot3],
% generate
meetings_pairs(Students, Slots),
% and test...
% constraint 1
memberchk(student1,Slot1),
% constraint 2
member(Sc2,Slots), memberchk(student2,Sc2), memberchk(student3,Sc2),
% constraint 3
forall(member(Sc3,Slots), \+((memberchk(student1,Sc3), memberchk(student4,Sc3)))),
% constraint 4
\+((memberchk(student6,Slot1) ; memberchk(student6,Slot3))).
meetings_pairs([], []).
meetings_pairs(Students, [[A,B]|Slots]) :-
select(A,Students,R1),
select(B,R1,R2),
A @< B,
meetings_pairs(R2,Slots).
yields
?- meetings_one_two_three(A,B,C).
A = [student1, student5],
B = [student4, student6],
C = [student2, student3] ;
false.
just, take care to use different Slot variables for constraints 2 and 3, because Variables are scoped to clause.
member
is too simplistic, and therefore slow/inelegant - want select
or actually a more flexible, custom variant of select
:
sched_slots(Slots) :-
% Create ordered list - and do not scramble the order
numlist(1, 6, Vars),
% student1 must meet in slot1
Slots = [s(1, S1Pos2), _, s(S3Pos1, S3Pos2)|_],
Not6 = [S1Pos2, S3Pos1, S3Pos2],
assign_slots(Vars, Slots),
% student2 and student3 must meet in the same slot
memberchk(s(2, 3), Slots),
% student1 and student4 cannot meet in the same slot
\+ memberchk(s(1, 4), Slots),
% student6 cannot meet in slot1 or slot3
\+ memberchk(6, Not6).
assign_slots([], []).
assign_slots([H|T], [s(Lower, Upper)|Slots]) :-
grab_2([H|T], Lower, Upper, Rem),
assign_slots(Rem, Slots).
grab_2(Vars, Lower, Upper, Rem) :-
select_forward_remainder_prev_tail(Lower, Vars, Forw, _, Rem, PrevTail),
% Preventing slow append by unifying PrevTail
select_forward_remainder_prev_tail(Upper, Forw, _, PrevTail, _, _).
% Based on select/3
select_forward_remainder_prev_tail(E, [H|T], F, R, P, PT) :-
select_forward_remainder_prev_tail_(T, H, E, F, R, P, PT).
select_forward_remainder_prev_tail_(T, H, H, T, T, PT, PT).
select_forward_remainder_prev_tail_([H|T], A, E, F, [A|R], [A|P], PT) :-
select_forward_remainder_prev_tail_(T, H, E, F, R, P, PT).
Result in swi-prolog:
?- time(sched_slots(Slots)).
% 362 inferences, 0.000 CPU in 0.000 seconds (95% CPU, 3766086 Lips)
Slots = [s(1, 5), s(4, 6), s(2, 3)] ;
% 108 inferences, 0.000 CPU in 0.000 seconds (91% CPU, 3348733 Lips)
false.
A demonstration of select_forward_remainder_prev_tail
:
?- select_forward_remainder_prev_tail(E, [1,2,3,4], F, R, P, T).
E = 1,
F = R, R = [2, 3, 4],
P = T ;
E = 2,
F = [3, 4],
R = [1, 3, 4],
P = [1|T] ;
E = 3,
F = [4],
R = [1, 2, 4],
P = [1, 2|T] ;
E = 4,
F = [],
R = [1, 2, 3],
P = [1, 2, 3|T].
Can also use clpfd:
:- use_module(library(clpfd)).
sched_slots_fd(Students) :-
% student1 must meet in slot1
S1 #= 1,
% student2 and student3 must meet in the same slot
Students = [S1, Same, Same, S4, _, S6],
% Each student must be in a slot
Students ins 1..3,
% student1 and student4 cannot meet in the same slot
S1 #\= S4,
% student6 cannot meet in slot1 or slot3
S6 #\= 1,
S6 #\= 3,
% Make vars ground
label(Students),
% Ensure 2 students per slot
msort(Students, [1, 1, 2, 2, 3, 3]).
Result in swi-prolog:
?- time(sched_slots_fd(Students)).
% 1,617 inferences, 0.000 CPU in 0.000 seconds (99% CPU, 4424730 Lips)
Students = [1, 3, 3, 2, 1, 2] ;
% 343 inferences, 0.000 CPU in 0.000 seconds (98% CPU, 2498780 Lips)
false.