Re: HElp

From: Mark Wallace <Mark.Wallace_at_infotech.monash.edu.au>
Date: Sun 24 Jul 2005 08:25:04 AM GMT
Message-id: <42E35060.2010205@infotech.monash.edu.au>
Hi Josee,

A quick reply:
* Job shop is NP-hard so no surprise that you can hit performance
problems on bigger problems
* You don't seem to use the special global constraints (e.g.
edge_finder) which are designed  to improve
    the efficiency of job shop problem solving
* Your search procedure is the most naive one.  Any scalability for
combinatorial optimisation
    requires you to think a bit about search heuristics

     Cheers
        Mark

PS You are recommended to use the libraries lib(ic) and lib(ic_global)
instead of lib(fd)

>am trying to solve the job shop problem using the
>folowing program writtem in eclipse.  the code works
>for small problems but takes forever to run when
>presented with larger prolems. How can i improve it?
>by forever here i mean more than 12 hours
>
>here is the code
>
>
>:- use_module(library(fd)).
>:- use_module(library(structures)).
>:- use_module(library(lists)).
>:- use_module(library(branch_and_bound)).
>
>
>:- mode read_data(++,-).
>:- mode output_data(++,+).
>:- local struct( taskstruct(name, jobno, duration,
>startime) ).
>
>
>% Input = Data= Problem
>% task Structure is task(id,duration,[task that it
>succeeds],machine to be run on
>% Variables are the start times of the various tasks.
>
>
>% This is the main predicate that finds the minimum
>schedule using the MIN_MAX predicate provided by the
>branch and bound library.
>
>  gp276(End, Variables, Time) :-
>    End :: [0..100000],
>         read_data('//c/JSSer/main/b.data',Input),
>         cputime(T0),
>         adddur(Input,Max), % calculate upper limit of
>start time domain
>         cls('others.data',""),
>          min_max((schedule(Input, End, Variables,Max),
>indomain(End)), End),
>    Time is cputime - T0,
>    return(End,Time),
>          output1(Variables).
>
>
>% read data from the input file
>read_data(File,Input):-
>    open(File,read,St),
>    read(St,X),
>    read_data_lp(St,X,Input),
>    close(St).
>read_data_lp(_St,end_of_file,[]):-
>    !.
>read_data_lp(St,X,[X|R]):-
>    read(St,Y),
>    read_data_lp(St,Y,R).
>
>% schedule program
>schedule(List, End, Variables,Max)   :-
>
>    makeVariables(List, Variables, End,Max),
>          precedences(List, Variables),
>          machines(List, Variables),
>          labeltasks(Variables),
>          writeterm('others.data',"Schedule
>\nTaskNo\tJobNo\tDuration\tStartTime\tFinishTime"),
>          writeto('others.data',Variables). % saves all
>the other possibles schedules.
>
>
>
>% add the durations to get the upper limit of the
>start times hence creating a finite domain
>
>adddur([],0).
>adddur([task(_,_,D,_,_)|T],Sum):- adddur(T,Sum1),Sum1
>#= Sum + (-D).
>
>
>
>% intializing domain variables
>makeVariables([],[],_,_).
>makeVariables([task(N,J,D,_,_)|Ts],
>[taskstruct(N,J,D,TS)|Js], End,Mx)  :-
>
>        TS :: [0..Mx],
>         TS + D #<= End, %Start time should be less
>than the finish time of the sschedule
>         makeVariables(Ts, Js, End,Mx).
>
>gettaskstruct(JL, J, N, D, TS)  :-
>once(member(taskstruct(N,J,D,TS), JL)). %extract a
>task from the list of tasks
>
>% checks the precedence constraints
>
>precedences([],_).
>precedences([task(N,J,_,Pre,_)|Ts], Variables)  :-
>        gettaskstruct(Variables,J, N, _, TS),
>        prectask(Pre, TS, Variables,J),
>        precedences(Ts, Variables).
>
>prectask([],  _, _,_).
>prectask([Name|Names], PostStart, Variables,Jn)  :-
>        gettaskstruct(Variables, Jn, Name, D, TS),
>        %(Jn #= JN ->
>        TS + D #<= PostStart,
>       % ;true ),         %precedence constraints
>        prectask(Names, PostStart, Variables,Jn).%
>start time + duration of
>                       %the previous task has to be
>                       %less than the start time of
>                       %the next task
>
>% check the machine constraints
>machines([], _).
>machines([task(N,J,_,_,M)|Ts], Variables)  :-
>        gettaskstruct(Variables, J, N, D, TS),
>        machtask(Ts, M, D, TS, Variables),
>        machines(Ts, Variables).
>
>machtask([], _, _, _, _).
>machtask([task(SN,J,_,_,M0)|Ts], M, D, TS, Variables)
>:-
>         (M == M0 ->
>             gettaskstruct(Variables, J, SN, SD, STS),
>             exclude(D, TS, SD, STS)
>         ; true ),
>        machtask(Ts, M, D, TS, Variables).
>
>% ensures that no two run the same task at the same
>time
>exclude(_D, TS, SD, STS)  :-  STS + SD #<= TS.
>%machine constraints
>exclude(D, TS, _SD, STS)  :-  TS + D #<= STS.
>
>labeltasks([]).
>labeltasks([taskstruct(_,_,_,TS)|Js])   :-
>      indomain(TS),
>      labeltasks(Js).
>
>
>% predicates to write to files
>writeto(File,[]):-!.
>writeto(File,[taskstruct(N,J,D,TS)|T]):-
>       output_data(File,J,N,D,TS),
>       writeto(File,T).
>
>
>cls(File,Term):-    open(File,write,St),
>          printf(St,"%s",Term),
>          close(St).
>
>
>writeterm(File,Term):-    open(File,append,St),
>          nl(St),
>          printf(St,"%s",Term),
>          nl(St),
>          close(St).
>
>
>output_data(File,J,N,D,TS):-  % writes task by task.
>          open(File,append,St),
>
>          writeq(St,N),
>          write(St,"    \t  "),
>          writeq(St,J),
>          write(St,"    \t  "),
>          writeq(St,D),
>          write(St,"    \t  "),
>          writeq(St,TS),
>          write(St,"    \t  "),
>          E #= TS + D,
>          writeq(St,E),
>          nl(St),
>          close(St).
>
>
>%predicates to return results to TCL
>output1([taskstruct(N,J,D,TS)|T]):-
>write_exdr(my_queue, taskstruct(N,J,D,TS)),
>                output1(T),
>                fail.
>
>
>output1([]):-   write_exdr(my_queue, end),
>       flush(my_queue).
>
>return(End,Time):-   write_exdr(resqueue, (End,Time)),
>          flush(resqueue).
>
>
>
>		
>____________________________________________________
>Start your day with Yahoo! - make it your home page
>http://www.yahoo.com/r/hs
>
>
>
>
>  
>


-- 
Mark Wallace
Faculty of Information Technology
Monash University
Building 63,
Clayton
Vic 3800
Australia
Tel: +61 3 9905 1367
Fax: +61 3 9905 8731
Received on Mon Jul 25 11:24:34 2005

This archive was generated by hypermail 2.1.8 : Wed 16 Nov 2005 06:07:38 PM GMT GMT