Constraint Values on Local Variable

210 views Asked by At

I'm currently working on a scheduling problem using the :- use_module(library(clpq)) library. My problem lies with retrieving the full solution to my problem statement.

schedule(BestSchedule, BestTotTime) :-          %BestSchedule of format [test(task,startTime,Duration Task, Core]
    (  findall(T,task(T),Tasks),
       findall(C,core(C),Cores),
       init_time,                               %Retract all facts of bestsofar(_,_)
       const_time(Tasks,Schedule,Cores,TotTime),%Here probably goes something wrong
       assign_processor(Schedule,Cores, TotTime),
       minimize(TotTime),
       update_time(Schedule, TotTime),  
       fail
    ;  bestsofar(BestSchedule,BestTotTime)
    ).

assign_processor([], _, _).  
assign_processor([task(T,S,D,C)|Rest], Cores, TotTime) :-
    assign_processor(Rest,Cores,TotTime),
    core(C),                            %Pick a core
    process_cost(T,C,D),                %Core/Task known, setting Duration (D)
    const_resource(task(T,S,D,C),Rest), %Setting extra constraints on chosen core 
    bestsofar(_,CurrentBestTime),       %Get current best time from fact bestsofar
    {TotTime < CurrentBestTime}.        %Set new constraint based on currentBestTime


const_resource(_,[]).
const_resource(Task,[Task2|Rest]) :- 
    no_data(Task,Task2),
    no_conflict(Task,Task2),            %No overlap on same processor
    const_resource(Task, Rest).         

no_conflict(task(_,S,D,C),task(_,S2,D2,C2)) :-
    C \== C2,!;                         %Tasks not on same processor
    { S+D =< S2;                        %Set no overlapping start/end times
     S2+D2 =< S }.  

no_data(task(T,S,D,C), task(T2,S2,D2,C2)) :-
         %depends_on(T,T2,_) = T2 needs to be finished before T can start
         %channel(C,C2,L,_) = Data transfer between cores generated latency L
         %Set no overlap including the latency if tasks are dependent
    depends_on(T,T2,_),channel(C,C2,L,_),!, { S2 + D2  =< S - L };
    depends_on(T2,T,_),!,channel(C2,C,L,_),!, { S + D   =< S2 - L};
    true.

init_time :-
    retract(bestsofar(_,_)), fail
    ;
    assert(bestsofar(foobar, 1000)).

update_time(Schedule,TotTime) :-
    retract(bestsofar(_,_)),!,
    assert(bestsofar(Schedule,TotTime)).

S = [task(t7, 100, 10, c1), task(t1, 0, 10, c1), task(t6, 75, 10, c1),
     task(t2, _G66, 10, c1), task(t4, 50, 10, c2), task(t3, 25, 10, c1),
     task(t5, 50, 10, c1)],
ET = 110.

This solution seems to be correct, but I don't have any specific value of task(t2, _G66, 10, c1) (tasknumber, start time, duration, processor core).

To my knowledge this is a local variable which values should be between 25<_G66<35 OR 60<_G66<75 but I can't seem to find a way to print these values in Prolog itself. I thought the minimize(TotTime) would force all variables be minimized which seems to happen with the rest.

Edit:

Added some more code to show where the problem should lie. No other failures are produced somewhere else. bestsofar/2 is used store the current best schedule solution and execution time. When we find a better, faster schedule we replace it using update_time/2. This searching will always fail, this way all possible solutions are tested. Once done we reach bestsofar(BestSchedule,BestTotTime) and return these values.

If I look at the debugger before returning the result.B=35-A which does support my manual test of 35<B<50 or 60<B<75. Can't really make the deduction myself because I don't know how to interpret the _ value in these constraints.

[ task(t7,100,10,c1),
  task(t1,0,10,c1),
  task(t6,75,10,c1),
  task(t2,B,10,c1),
  task(t4,50,10,c2),
  task(t3,25,10,c1),
  task(t5,50,10,c1)
], % with constraints
    {}(_ = -55 - A ',' _ = -40 - A ',' _ = -25 + A ',' _ = -10 + A ',' _ = -30 - A ',' _ = -5 - A ',' A >= -5 ',' A =< 0 ',' _ = -55 - A ',' _ = -25 + A ',' _ = 65 + A ',' B = 35 - A)

Without no_data/2 my code does work for examples where no channel latency is used. Therefore I guess any problem should lie in that piece of code.

Runnable code if interested: http://pastebin.com/3PmRu7Aq

1

There are 1 answers

1
Timbo925 On BEST ANSWER

After some searching I found the problem. The code was able to generate the correct schedule from the beginning. The problem was only the Starting 'start times' of the tasks were minimized if they needed to be for minimize(TotTime)

Therefore if a certain task was not crucial to the critical path, the start time was't defined in the solution. This was solvable by iterating trough the result and minimizing each StartTime

minimize_schedule([]).
minimize_schedule([task(_,Start,_,_)|Rest]) :-
    minimize(Start), 
    minimize_schedule(Rest).