Skip to content
Snippets Groups Projects

Resolve "complete mini project 2"

Merged aalbert requested to merge 7-complete-mini-project-2 into main
1 file
+ 0
1
Compare changes
  • Side-by-side
  • Inline
+ 103
0
% Student exercise profile
:- set_prolog_flag(occurs_check, error). % disallow cyclic terms
:- use_module(library(clpfd)).
jobshop10_5(Time, Schedule) :-
Schedule = [[(_,1,21),(_,0,53),(_,4,95),(_,3,55),(_,2,34)],
[(_,0,21),(_,3,52),(_,4,16),(_,2,26),(_,1,71)],
[(_,3,39),(_,4,98),(_,1,42),(_,2,31),(_,0,12)],
[(_,1,77),(_,0,55),(_,4,79),(_,2,66),(_,3,77)],
[(_,0,83),(_,3,34),(_,2,64),(_,1,19),(_,4,37)],
[(_,1,54),(_,2,43),(_,4,79),(_,0,92),(_,3,62)],
[(_,3,69),(_,4,77),(_,1,87),(_,2,87),(_,0,93)],
[(_,2,38),(_,0,60),(_,1,41),(_,3,24),(_,4,83)],
[(_,3,17),(_,1,49),(_,4,25),(_,0,44),(_,2,98)],
[(_,4,77),(_,3,79),(_,2,43),(_,1,75),(_,0,96)]],
jobshop(10, 5, Time, Schedule).
jobshop3_3(Time, Schedule) :-
Schedule = [[(_,0,3), (_,1,2), (_,2,2)],
[(_,0,2), (_,2,1), (_,1,4)],
[(_,0,4), (_,1,4), (_,2,3)]],
jobshop(3, 3, Time, Schedule).
jobshop2_1(Time, Schedule) :-
Schedule = [[(_,0,3)],
[(_,0,2)]],
jobshop(2, 1, Time, Schedule).
jobshop(N, M, Time, Jobs) :-
% assert the given jobs have the expected size
length(Jobs, N),
maplist(inv_length(M), Jobs),
% assert that the tasks are done in the right order
maplist(order_tasks(Time), Jobs),
% assert that jobs on machines do not overlap
maplist(remove_overlap(Jobs), Jobs),
% 10000 is used as an upper bound.
% Ideally, an upper bound should be retrieved from the problem.
get_vars(Time, Jobs, Vars),
Time in 0..10000,
labeling([ffc, enum, min(Time)], Vars).
% Get the variables of th problem
get_vars(Time, Jobs, Vars) :-
get_vars_(Jobs, FJobs),
Vars = [Time|FJobs].
get_vars_([], []).
get_vars_([[(H,_,_)|Tl]|Tl1], [H|Tl2]) :-
get_vars_([Tl|Tl1], Tl2).
get_vars_([[]|Tl], Tl1) :-
get_vars_(Tl, Tl1).
% Get the length of a list
inv_length(N, L) :- length(L, N).
order_tasks(Time, [Task|Tasks]) :-
% First task is done after 0 unit of time.
Task = (T,_,_),
T #>= 0,
order_tasks_(Time, [Task|Tasks]).
% Last task finish before the total needed time.
order_tasks_(Time, [Task|[]]) :-
Task = (T,_,D),
Time #>= T+D.
% Every task begin after the previous one is done.
order_tasks_(Time, [(T,_,D),Task|Tasks]) :-
Task = (T1,_,_),
T+D #=< T1,
order_tasks_(Time, [Task|Tasks]).
remove_overlap(Jobs, Tasks) :-
select(Tasks, Jobs, RemainJobs),
maplist(remove_overlap_1(RemainJobs), Tasks).
remove_overlap_1(RemainsJobs, Task) :-
maplist(remove_overlap_2(Task), RemainsJobs).
remove_overlap_2((_,_,0), _).
remove_overlap_2((T,M,D), [(T1,M,_)|_]) :-
D \= 0,
Len is D-1,
numlist(0, Len, L),
maplist(add_constraint(T, T1), L).
remove_overlap_2((T,M,D), [(_,M1,_)|Tasks]) :-
M \= M1,
remove_overlap_2((T,M,D), Tasks).
add_constraint(T, T1, D) :-
T+D #\= T1.
%?- jobshop_3_3(Time, Schedule).
Loading