在this article之后,我一直在处理一个调度问题,该问题引用了this program,并试图将其归纳为七个班次。我不愿采用所采用的标签策略,因为我不确定如何在合理的时间范围内对其进行优化以报告结果。
要点是,将生成一个地图,其中包含人员的所有组合,轮班以填补(f)和每次轮班要执行的任务(t),从而得出s f t变量,然后将其标记为1或0表示已分配或未分配。
该示例使用3名员工,每个班次执行11个班次,每个班次执行多个任务,并且运行速度非常快,可以生成可能的解决方案。
但是,即使只考虑20班次,每班6名员工完成1个任务,贴标签也花费了不合理的时间。
从某种意义上说,这应该是正常现象吗?随着复杂性的增加,这种性能下降?
我可以采用一种更优雅的策略吗?
12月19日修改:
更多地考虑这一点,我认为问题在于这种情况下的标签效率低下,因为我不知道如何创建排名机制来协助默认的标签策略,因为地图正在处理reified(域为0..1)变量。
我认为我的选择是:
a)添加一些变量来辅助标注策略,使其表现得比暴力策略更好。
b)创建自定义标签策略。 (对此,我们将不胜感激)
-代码:
:- 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]).