Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Expressing setup time with cumulatives

There are many families of scheduling problems. I'm looking into a problem where I have families of jobs/tasks where the transition from one family to another family require reconfiguring the machine (setup time).

I'm using cumulatives[2/3] to solve this problem, but I feel unsure how the setup time could be expressed.

In this small example I have 10 tasks belonging to 3 different families. Any task can run on any machine, but a switch from one task in one family to another task in another family require a setup-time to be added.

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

go( Ss, Es, Ms, Tm, Lab ) :-

    Ss = [S1, S2, S3, S4,S5,S6,S7,S8,S9,S10], %Starttimes
    Es = [E1, E2, E3, E4,E5,E6,E7,E8,E9,E10], %Endtimeds
    Ms = [M1, M2, M3, M4,M5,M6,M7,M8,M9,M10], %MachineIds



    domain(Ss, 1, 30),
    domain(Es, 1, 30),
    domain(Ms, 1, 3 ),

    Tasks = [
        %Family 1: Setuptime, Su1 = 4, 
        task(  S1, 6,  E1,  1, M1 ),  %Task T1
        task(  S2, 6,  E2,  1, M2 ),  %Task T2
        task(  S3, 3,  E3,  1, M3 ),  %Task T3
        task(  S4, 7,  E4,  1, M4 ),  %Task T4
        %Family 2: Setuptime, Su2 = 3 
        task(  S5, 5,  E5,  1, M5 ),  %Task T5
        task(  S6, 8,  E6,  1, M6 ),  %Task T6
        task(  S7, 4,  E7,  1, M7 ),  %Task T7
        %Family 3: Setuptime, Su3 = 5 
        task(  S8, 4,  E8,  1, M8 ),  %Task T8
        task(  S9, 4,  E9,  1, M9 ),  %Task T9
        task( S10, 5,  E10, 1, M10 )  %Task T10
    ],

    %All machines has resource capacity = 1
    Machines = [
        machine(  1, 1 ), %M1
        machine(  2, 1 ), %M2
        machine(  3, 1 )  %M3
    ],

    cumulatives(Tasks, Machines, [bound(upper),task_intervals(true)] ),

    maximum( MaxEndTime, Es ),

    %Make the list of options to pass to the labeling predicate
    append( [ [minimize(MaxEndTime)], [time_out( Tm, _)], Lab ], LabOpt ),
    Vars=[S1,M1,S2,M2,S3,M3,S4,M4,S5,M5,S6,M6,S7,M7,S8,M8,S9,M9,S10,M10],
    labeling( LabOpt, Vars). 

One valid schedule ( but not optimal ) could be:

M1: Su1,T1,T2,Su3,T10
M2: Su2,T5,T6,Su3,T8
M3: Su1,T3,T4,Su2,T7,Su3,T9

How is the best way to express this together with use of cumulatives[2/3]? By making the duration of each task a domain variable and adding extra constraints to it?

like image 917
MortenM Avatar asked May 23 '14 06:05

MortenM


1 Answers

First, cumulatives/[2,3] doesn't have an option for expression setup times, so one has to post explicit constraints expressing "if two tasks of different families run on the same machine, then there must be a gap between the end of the predecessor task and the start of the successor task".

This can be encoded by calling:

setups(Ss, Ms, [6,6,3,7,5,8,4,4,4,5], [1,1,1,1,2,2,2,3,3,3], [4,4,4,4,3,3,3,5,5,5]),

defined as:

% post setup constraints for start times Ss, machines Ms, durations
% Ds, task families Fs, and setup times Ts
setups(Ss, Ms, Ds, Fs, Ts) :-
    (   fromto(Ss,[S1|Ss2],Ss2,[]),
        fromto(Ms,[M1|Ms2],Ms2,[]),
        fromto(Ds,[D1|Ds2],Ds2,[]),
        fromto(Fs,[F1|Fs2],Fs2,[]),
        fromto(Ts,[T1|Ts2],Ts2,[])
    do  (   foreach(S2,Ss2),
            foreach(M2,Ms2),
            foreach(D2,Ds2),
            foreach(F2,Fs2),
            foreach(T2,Ts2),
            param(S1,M1,D1,F1,T1)
        do  (   F1 = F2 -> true
            ;   % find forbidden interval for S2-S1 if on same machine
                L is 1-(T1+D2),
                U is (T2+D1)-1,
                StartToStart in \(L..U),
                (M1#\=M2 #\/ S2 - S1 #= StartToStart)
            )
        )
    ).

Secondly, if the machines are interchangeable as in your example, you can break symmetries by imposing that 1 should occur before 2 and 2 should occur before 3 in Ms:

value_order(Ms),

defined as:

value_order(Ms) :-
    automaton(Ms, [source(q0),sink(q0),sink(q1),sink(q2)],
              [arc(q0,1,q1),
               arc(q1,1,q1), arc(q1,2,q2),
               arc(q2,1,q2), arc(q2,2,q2), arc(q2,3,q2)]).

Thirdly, fixing all machines before all start times is a much better search strategy. Yet another refinement is to (a) fix the machines, (b) narrow the intervals of the tasks enough to impose an order per machine, (c) fix the start times:

    Q1 #= S1/6,
    Q2 #= S2/6,
    Q3 #= S3/3,
    Q4 #= S4/7,
    Q5 #= S5/5,
    Q6 #= S6/8,
    Q7 #= S7/4,
    Q8 #= S8/4,
    Q9 #= S9/4,
    Q10 #= S10/5,
    labeling([minimize(MaxEndTime)/*,time_out( Tm, _)*/|Lab],
             [M1,M2,M3,M4,M5,M6,M7,M8,M9,M10,
              Q1,Q2,Q3,Q4,Q5,Q6,Q7,Q8,Q9,Q10,
              S1,S2,S3,S4,S5,S6,S7,S8,S9,S10]).

With these changes, the optimal solution with proof of optimality is obtained in some 550ms:

| ?- statistics(runtime,_), go(Ss,Es,Ms,_,[step]), statistics(runtime,R).
Ss = [1,7,1,13,7,12,17,1,5,9],
Es = [7,13,4,20,12,20,21,5,9,14],
Ms = [1,1,2,1,2,2,3,3,3,3],
R = [1621540,550] ? 
yes
like image 72
Mats Carlsson Avatar answered Oct 16 '22 10:10

Mats Carlsson