1

I have been crunching through a scheduling problem following this article which references this program and trying to generalize it past the seven shifts. I am getting hung up on the labelling strategy employed because I am not sure how it could be optimized to report results in a reasonable time frame.

The gist is, a map is generated of all the combinations of staff (s), shifts to fill (f), and tasks (t) to be performed on each shift, which results in sft variables which then are either labeled 1 or 0 to represent assigned or not assigned.

The example uses 3 staff, with 11 shifts with several tasks per shift and runs really fast to generate a possible solution.

But labelling takes an unreasonable amount of time when even considering as few as 20 shifts with 1 task per shift with 6 staff.

Is this normal in the sense I should expect this performance loss with this increased complexity?

Is there a more elegant strategy I could look at to employ?


Dec 19 edit:

Looking into this more, I think the problem is that labelling in this context is inefficient since I don't know how to create a ranking mechanism to assist the default labelling strategy since the map is dealing with reified (with a domain of 0..1) variables.

I think my options are:

a) add some variable to assist the labeling strategy to make it so it behaves better than a bruteforce strategy.

b) create a custom labeling strategy. (any resources on this would be appreciated)

-- The code:

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

:- dynamic employee/1.
:- dynamic employee_max_shifts/2.
:- dynamic employee_skill/2.
:- dynamic task_skills/2.
:- dynamic employee_unavailable/2.
:- dynamic task/2.
:- dynamic employee_assigned/2.

employee(micah).
employee(jonathan).
employee(blake).
employee(barry).
employee(jerry).
employee(larry).
employee(gary).

employee_max_shifts(micah,      14).
employee_max_shifts(jonathan,   14).
employee_max_shifts(blake,      14).
employee_max_shifts(barry,      14).
employee_max_shifts(jerry,      14).
employee_max_shifts(larry,      14).
employee_max_shifts(gary,       14).

employee_skill(micah,   programming).
employee_skill(barry,   programming).
employee_skill(jerry,   programming).
employee_skill(larry,   programming).
employee_skill(gary,    programming).
employee_skill(jonathan,programming).
employee_skill(blake,   programming).

task_skills(web_design,[programming]).

shifts([
    shift(1,1),shift(1,2),
    shift(2,1),shift(2,2),
    shift(3,1),shift(3,2),
    shift(4,1),shift(4,2),
    shift(5,1),shift(5,2),
    shift(6,1),shift(6,2),
    shift(7,1),shift(7,2),
    shift(8,1),shift(8,2),
    shift(9,1),shift(9,2),
    shift(10,1),shift(10,2),
    shift(11,1),shift(11,2),
    shift(12,1),shift(12,2),
    shift(13,1),shift(13,2),
    shift(14,1),shift(14,2),
    shift(15,1),shift(15,2),
    shift(16,1),shift(16,2),
    shift(17,1),shift(17,2),
    shift(18,1),shift(18,2),
    shift(19,1),shift(19,2),
    shift(20,1),shift(20,2),
    shift(21,1),shift(21,2),
    shift(22,1),shift(22,2),
    shift(23,1),shift(23,2),
    shift(24,1),shift(24,2),
    shift(25,1),shift(25,2),
    shift(26,1),shift(26,2),
    shift(27,1),shift(27,2),
    shift(28,1),shift(28,2)]).

task(web_design,shift('1',1)).
task(web_design,shift('1',2)).
task(web_design,shift('2',1)).
task(web_design,shift('2',2)).
task(web_design,shift('3',1)).
task(web_design,shift('3',2)).
task(web_design,shift('4',1)).
task(web_design,shift('4',2)).
task(web_design,shift('6',1)).
task(web_design,shift('6',2)).
task(web_design,shift('7',1)).
task(web_design,shift('7',2)).
task(web_design,shift('8',1)).
task(web_design,shift('8',2)).
task(web_design,shift('9',1)).
task(web_design,shift('9',2)).
task(web_design,shift('10',1)).
task(web_design,shift('10',2)).
task(web_design,shift('11',1)).
task(web_design,shift('11',2)).
task(web_design,shift('12',1)).
task(web_design,shift('12',2)).
task(web_design,shift('13',1)).
task(web_design,shift('13',2)).
task(web_design,shift('14',1)).
task(web_design,shift('14',2)).
task(web_design,shift('15',1)).
task(web_design,shift('15',2)).
task(web_design,shift('16',1)).
task(web_design,shift('16',2)).
task(web_design,shift('17',1)).
task(web_design,shift('17',2)).
task(web_design,shift('18',1)).
task(web_design,shift('18',2)).
task(web_design,shift('19',1)).
task(web_design,shift('19',2)).
task(web_design,shift('20',1)).
task(web_design,shift('20',2)).
task(web_design,shift('21',1)).
task(web_design,shift('21',2)).
task(web_design,shift('22',1)).
task(web_design,shift('22',2)).
task(web_design,shift('23',1)).
task(web_design,shift('23',2)).
task(web_design,shift('24',1)).
task(web_design,shift('24',2)).
task(web_design,shift('25',1)).
task(web_design,shift('25',2)).
task(web_design,shift('26',1)).
task(web_design,shift('26',2)).
task(web_design,shift('27',1)).
task(web_design,shift('27',2)).
task(web_design,shift('28',1)).
task(web_design,shift('28',2)).

% get_employees(-Employees)
get_employees(Employees) :-
    findall(employee(E),employee(E),Employees).
% get_tasks(-Tasks)
get_tasks(Tasks) :-
    findall(task(TName,TShift),task(TName,TShift),Tasks).

% create_assoc_list(+Employees,+Tasks,-Assoc)
% Find all combinations of pairs and assign each a variable to track
create_assoc_list(Es,Ts,Assoc) :-
    empty_assoc(EmptyAssoc),
    findall(assign(E,T),(member(E,Es),member(T,Ts)),AssignmentPairs),
    build_assoc_list(EmptyAssoc,AssignmentPairs,Assoc).

% build_assoc_list(+AssocAcc,+Pairs,-Assoc)
build_assoc_list(Assoc,[],Assoc).
build_assoc_list(AssocAcc,[Pair|Pairs],Assoc) :-
    put_assoc(Pair,AssocAcc,_Var,AssocAcc2),
    build_assoc_list(AssocAcc2,Pairs,Assoc).

% assoc_keys_vars(+Assoc,+Keys,-Vars)
%
% Retrieves all Vars from Assoc corresponding to Keys.
% (Note: At first it seems we could use a fancy findall in place of this, but findall
% will replace the Vars with new variable references, which ruins our map.)
assoc_keys_vars(Assoc, Keys, Vars) :-
        maplist(assoc_key_var(Assoc), Keys, Vars).
assoc_key_var(Assoc, Key, Var) :- get_assoc(Key, Assoc, Var).

% list_or(+Exprs,-Disjunction)
list_or([L|Ls], Or) :- foldl(disjunction_, Ls, L, Or).
disjunction_(A, B, B#\/A).

get_assoc_values_in_employee_order(Es, Ts, Assoc, Values) :-
    findall(assign(E,T),(member(E,Es), member(T,Ts)),AssignmentPairs),
    assoc_keys_vars(Assoc, AssignmentPairs,Values).

% schedule(-Schedule)
%
% Uses clp(fd) to generate a schedule of assignments, as a list of assign(Employee,Task)
% elements. Adheres to the following rules:
% (1) Every task must have at least one employee assigned to it.
% (2) No employee may be assigned to multiple tasks in the same shift.
% (3) No employee may be assigned to more than their maximum number of shifts.
% (4) No employee may be assigned to a task during a shift in which they are unavailable.
% (5) No employee may be assigned to a task for which they lack necessary skills.
% (6) Any pre-existing assignments (employee_assigned) must still hold.
schedule(Schedule) :-
    writeln('Building constraints'),
    get_employees(Es),
    get_tasks(Ts),
    create_assoc_list(Es,Ts,Assoc),
    assoc_to_keys(Assoc,AssocKeys),
    assoc_to_values(Assoc,AssocValues),
    constraints(Assoc,Es,Ts),

    label(AssocValues),

    findall(AssocKey,(member(AssocKey,AssocKeys),get_assoc(AssocKey,Assoc,1)),Assignments),
    Schedule = Assignments.

% constraints(+Assoc,+Employees,+Tasks)
constraints(Assoc,Es,Ts) :-
    core_constraints(Assoc,Es,Ts),
    simul_constraints(Assoc,Es,Ts),
    max_shifts_constraints(Assoc,Es,Ts),
    unavailable_constraints(Assoc,Es,Ts),
    skills_constraints(Assoc,Es,Ts),
    assigned_constraints(Assoc).

% core_constraints(+Assoc,+Employees,+Tasks)
%
% Builds the main conjunctive sequence of the form:
% (A_e(0),t(0) \/ A_e(1),t(0) \/ ...) /\ (A_e(0),t(1) \/ A_e(1),t(1) \/ ...) /\ ...
core_constraints(Assoc,Es,Ts) :-
    maplist(core_constraints_disj(Assoc,Es),Ts).

% core_constraints_disj(+Assoc,+Employees,+Task)
% Helper for core_constraints, builds a disjunction of sub-expressions, such that
% at least one employee must be assigned to Task
core_constraints_disj(Assoc,Es,T) :-
    findall(assign(E,T),member(E,Es),Keys),
    assoc_keys_vars(Assoc,Keys,Vars),
    list_or(Vars,Disj),
    Disj.


% simul_constraints(+Assoc,+Employees,+Tasks)
%
% Builds a constraint expression to prevent one person from being assigned to multiple
% tasks at the same time. Of the form:
% (A_e(0),t(n1) + A_e(0),t(n2) + ... #=< 1) /\ (A_e(1),t(n1) + A_e(1),t(n2) + ... #=< 1)
% where n1,n2,etc. are indices of tasks that occur at the same time.
simul_constraints(Assoc,Es,Ts) :-
    shifts(Shifts),
    findall(employee_shift(E,Shift),(member(E,Es),member(Shift,Shifts)),EmployeeShifts),
    maplist(simul_constraints_subexpr(Assoc,Ts),EmployeeShifts).

simul_constraints_subexpr(Assoc,Ts,employee_shift(E,Shift)) :-
    findall(task(TName,Shift),member(task(TName,Shift),Ts),ShiftTs),
    findall(assign(E,T),member(T,ShiftTs),Keys),
    assoc_keys_vars(Assoc,Keys,Vars),
    sum(Vars,#=<,1).


% max_shifts_constraints(+Assoc,+Employees,+Tasks)
%
% Builds a constraint expression that prevents employees from being assigned too many
% shifts. Of the form:
% (A_e(0),t(0) + A_e(0),t(1) + ... #=< M_e(0)) /\ (A_e(1),t(0) + A_e(1),t(1) + ... #=< M_e(1)) /\ ...
% where M_e(n) is the max number of shifts for employee n.
max_shifts_constraints(Assoc,Es,Ts) :-
    maplist(max_shifts_subexpr(Assoc,Ts),Es).

max_shifts_subexpr(Assoc,Ts,E) :-
    E = employee(EName),
    employee_max_shifts(EName,MaxShifts),
    findall(assign(E,T),member(T,Ts),Keys),
    assoc_keys_vars(Assoc,Keys,Vars),
    sum(Vars,#=,MaxShifts).


% unavailable_constraints(+Assoc,+Employees,+Tasks)
%
% For every shift for which an employee e(n) is unavailable, add a constraint of the form
% A_e(n),t(x) = 0 for every t(x) that occurs during that shift. Note that 0 is equivalent
% to False in clp(fd).
unavailable_constraints(Assoc,Es,Ts) :-
    findall(assign(E,T),(
            member(E,Es),
            E = employee(EName),
            employee_unavailable(EName,Shift),
            member(T,Ts),
            T = task(_TName,Shift)
        ),Keys),
    assoc_keys_vars(Assoc,Keys,Vars),
    maplist(#=(0),Vars).


% skills_constraints(+Assoc,+Employees,+Tasks)
%
% For every task t(m) for which an employee e(n) lacks sufficient skills, add a
% constraint of the form A_e(n),t(m) = 0.
skills_constraints(Assoc,Es,Ts) :-
    findall(assign(E,T),(
            member(T,Ts),
            T = task(TName,_TShift),
            task_skills(TName,TSkills),
            member(E,Es),
            \+employee_has_skills(E,TSkills)
        ),Keys),
    assoc_keys_vars(Assoc,Keys,Vars),
    maplist(#=(0),Vars).


% employee_has_skills(+Employee,+Skills)
%
% Fails if Employee does not possess all Skills.
employee_has_skills(employee(EName),Skills) :-
    findall(ESkill,employee_skill(EName,ESkill),ESkills),
    subset(Skills,ESkills).


% assigned_constraints(+Assoc)
%
% For every task t(m) to which an employee e(n) is already assigned, add a constraint
% of the form A_e(n),t(m) = 1 to force the assignment into the schedule. Note that
% we execute this constraint inline here instead of collecting it into a Constraint list.
assigned_constraints(Assoc) :-
    findall(assign(E,T),(
            employee_assigned(EName,T),
            E = employee(EName)
        ),Keys),
    assoc_keys_vars(Assoc,Keys,Vars),
    maplist(#=(1),Vars).




task_skills(web_design,[programming]).
false
  • 10,264
  • 13
  • 101
  • 209
Tim Austin
  • 31
  • 1
  • 6
  • 1
    Are you sure this is a performance problem and not some looping? Temporally replace `labeling/2` by `false` just to see if your program terminates. See [tag:failure-slice] for more. – false Dec 18 '18 at 14:55
  • 1
    I believe it is, I replaced the label with a false, and it terminates promptly. I have further suspicion towards labelling performance because when I interrupt the program and trace the call stack it's working through clp predicates. – Tim Austin Dec 18 '18 at 15:21
  • Since I am using SWI prolog for this, I have read that it is right that I should expect it to terminate if it makes it to the label stage, is that correct? Is there a way to see in the trace or call stack what the current state of the label variables are? – Tim Austin Dec 19 '18 at 15:20
  • 1
    You are right: `library(clpfd)` in SWI has the guarantee that `labeling/2` always terminates. – false Dec 19 '18 at 19:47
  • 1
    As for a trace: This will certainly confuse you more that you might think. But you could try to label some variables first and then the others etc. – false Dec 19 '18 at 19:48
  • I think based on this, I know there only a handful of labelling sub patterns that will be accepted by the constraints, is there an approach to take where I could label several other unknowns based on the labelled value of the current variable? Following this answer (https://stackoverflow.com/a/36266040/8583288) I believe I could create a custom label predicate, but how do i assign the values to make use of backtracking? – Tim Austin Jan 02 '19 at 05:57
  • At least, take into account the [other answer](https://stackoverflow.com/a/36261381/772868), too! – false Jan 02 '19 at 13:48

0 Answers0