Initializing help system before first use

B. Scheduling problems


Description:

Problem name and type, features Difficulty Related examples
B‑1 Construction of a stadium: Project scheduling (Method of Potentials) *** projplan_graph.mos
2 problems; selection with `|', sparse/dense format, naming and redefining constraints, subroutine: procedure for solution printing, forward declaration, array of set
B‑2 Flow shop scheduling **** flowshop_graph.mos
alternative formulation using SOS1
B‑3 Job shop scheduling *** jobshop_graph.mos
formulating disjunctions (BigM); dynamic array, range, exists, forall-do,array of set, array of list
B‑4 Sequencing jobs on a bottleneck machine: Single machine scheduling *** sequencing_graph.mos
3 different objectives; subroutine: procedure for solution printing, localsetparam, if-then
B‑5 Paint production: Asymmetric Traveling Salesman Problem (TSP) ***
solution printing, repeat-until, cast to integer, selection with `|', round
B‑6 Assembly line balancing ** linebal_graph.mos
encoding of arcs, range


File(s): b1stadium.mos (Mar. 2002), b1stadium2.mos (Jan. 2006), b2flowshop.mos (Mar. 2002), b3jobshop.mos (Mar. 2002), b3jobshop2.mos (Mar. 2002), b3jobshop3.mos (Jan. 2006), b4seq.mos (Mar. 2002), b5paint.mos (Mar. 2002), b6linebal.mos (Mar. 2002)
Data file(s): b1stadium.dat, b1stadium2.dat, b2flowshop.dat, b3jobshop.dat, b3jobshop2.dat, b3jobshop3.dat, b4seq.dat, b5paint.dat, b6linebal.dat

b1stadium.mos
(!******************************************************
   Mosel Example Problems
   ======================

   file b1stadium.mos
   ``````````````````
   Construction of a stadium

   A town is planning to build a new stadium and need to
   determine the earliest it can be completed. Additionally,
   the town would like to project to finish earlier than the
   initial estimate. The town is prepared to pay the builder
   a bonus for every week the project completes early. Each
   task has a max week reduction with added costs. The
   second problem determines when the project will finish
   if the builder maximizes their profit.

   The first problem is a classical project scheduling problem.
   To define the relationship between tasks, we create an array
   'ARC' and define constraints for related tasks. The second
   problem is called 'scheduling with project crashing' and it
   requires the result of the first problem. The new variable
   'advance' is introduced to represent how many weeks early 
   each task can be finished.
   
   (c) 2008 Fair Isaac Corporation
       author: S. Heipcke, Mar. 2002, rev. Oct 2009
*******************************************************!)

model "B-1 Stadium construction"
 uses "mmxprs"
 
 forward procedure printsol
 
 declarations   
  N = 19                              ! Number of tasks in the project 
                                      ! (last = fictitious end task)
  TASKS=1..N
  ARC: dynamic array(TASKS,TASKS) of real  ! Matrix of the adjacency graph 
  DUR: array(TASKS) of real           ! Duration of tasks
  start: array(TASKS) of mpvar        ! Start times of tasks
  obj1: real                          ! Solution of first problem
 end-declarations

 initializations from 'b1stadium.dat'
  ARC DUR
 end-initializations
 
! Precedence relations between tasks
 forall(i,j in TASKS | exists(ARC(i,j)))  
  Prec(i,j):= start(j) - start(i) >= DUR(i)

! Solve the first problem: minimize the total duration
 minimize(start(N))
 obj1:=getobjval
 
! Solution printing
 printsol

! **** Extend the problem ****
 declarations
  BONUS: integer                      ! Bonus per week finished earlier
  MAXW: array(TASKS) of real          ! Max. reduction of tasks (in weeks)
  COST: array(TASKS) of real          ! Cost of reducing tasks by a week 
  advance: array(TASKS) of mpvar      ! Number of weeks finished early
 end-declarations 

 initializations from 'b1stadium.dat'
  MAXW BONUS COST
 end-initializations

! Second objective function
 Profit:= BONUS*advance(N) - sum(i in 1..N-1) COST(i)*advance(i)

! Redefine precedence relations between tasks
 forall(i,j in TASKS | exists(ARC(i,j)))  
  Prec(i,j):= start(j) - start(i) + advance(i) >= DUR(i)

! Total duration
 start(N) + advance(N) = obj1

! Limit on number of weeks that may be saved
 forall(i in 1..N-1) advance(i) <= MAXW(i)

! Solve the second problem: maximize the total profit
 maximize(Profit) 
 
! Solution printing
 writeln("Total profit: ", getsol(Profit))
 printsol

!-----------------------------------------------------------------

 procedure printsol
  writeln("Total duration: ", getsol(start(N)), " weeks")
  forall(i in 1..N-1)
   write(strfmt(i,2), ": ", strfmt(getsol(start(i)),-3),
    if(i mod 9 = 0,"\n",""))
  writeln
 end-procedure

end-model  

b1stadium2.mos
(!******************************************************
   Mosel Example Problems
   ======================

   file b1stadium2.mos
   ```````````````````
   Construction of a stadium
   - Set version -

   A town is planning to build a new stadium and need to
   determine the earliest it can be completed. Additionally,
   the town would like to project to finish earlier than the
   initial estimate. The town is prepared to pay the builder
   a bonus for every week the project completes early. Each
   task has a max week reduction with added costs. The
   second problem determines when the project will finish
   if the builder maximizes their profit.

   The first problem is a classical project scheduling problem.
   To define the precedence relations between tasks, we work 
   with an array 'SUCC' that holds the set of direct successors   
   per task and define constraints for related tasks. The second
   problem is called 'scheduling with project crashing' and it
   requires the result of the first problem. The new variable
   'advance' is introduced to represent how many weeks early 
   each task can be finished.

   (c) 2008-2022 Fair Isaac Corporation
       author: S. Heipcke, Jan. 2006, rev. Mar. 2022
*******************************************************!)

model "B-1 Stadium construction (2)"
 uses "mmxprs"
 
 forward procedure printsol
 
 declarations   
  N = 19                                ! Number of tasks in the project 
                                        ! (last = fictitious end task)
  TASKS=1..N
  SUCC: array(TASKS) of set of integer  ! Successors of tasks 
  DUR: array(TASKS) of real             ! Duration of tasks
  start: array(TASKS) of mpvar          ! Start times of tasks
  obj1: real                            ! Solution of first problem
 end-declarations

 initializations from 'b1stadium2.dat'
  SUCC DUR
 end-initializations
 
! Precedence relations between tasks
 forall(i in TASKS, j in SUCC(i))  
  Prec(i,j):= start(j) - start(i) >= DUR(i)

! Solve the first problem: minimize the total duration
 minimize(start(N))
 obj1:=getobjval
 
! Solution printing
 printsol

! **** Extend the problem ****
 declarations
  BONUS: integer                      ! Bonus per week finished earlier
  MAXW: array(TASKS) of real          ! Max. reduction of tasks (in weeks)
  COST: array(TASKS) of real          ! Cost of reducing tasks by a week 
  advance: array(TASKS) of mpvar      ! Number of weeks finished early
 end-declarations 

 initializations from 'b1stadium2.dat'
  MAXW BONUS COST
 end-initializations

! Second objective function
 Profit:= BONUS*advance(N) - sum(i in 1..N-1) COST(i)*advance(i)

! Redefine precedence relations between tasks
 forall(i in TASKS, j in SUCC(i))  
  Prec(i,j):= start(j) - start(i) + advance(i) >= DUR(i)

! Total duration
 start(N) + advance(N) = obj1

! Limit on number of weeks that may be saved
 forall(i in 1..N-1) advance(i) <= MAXW(i)

! Solve the second problem: maximize the total profit
 maximize(Profit) 
 
! Solution printing
 writeln("Total profit: ", getsol(Profit))
 printsol

!-----------------------------------------------------------------

 procedure printsol
  writeln("Total duration: ", getsol(start(N)), " weeks")
  forall(i in 1..N-1)
   write(strfmt(i,2), ": ", strfmt(getsol(start(i)),-3),
    if(i mod 9 = 0,"\n",""))
  writeln
 end-procedure

end-model  

b2flowshop.mos
(!******************************************************
   Mosel Example Problems
   ======================

   file b2flowshop.mos
   ```````````````````
   Flow shop production planning
   
   A workshop has three machines to produce metal pipes.
   A piece must go through each machine and cannot stop
   unless it is between machines. What is the best order
   of pieces so that the total time for completion is minimized
   for all pieces?
   
   This problem uses four variables to track which job is scheduled
   in which position, which machines are empty, which jobs are 
   waiting between machines, and when jobs are starting.
   Note that each job must be assigned a position and every
   position ('rank) must be assigned a job. The 'rank' variables
   are either binary variables or defined as members of two SOS-1.
   
   (c) 2008-2022 Fair Isaac Corporation
       author: S. Heipcke, Mar. 2002, rev. Mar. 2022
*******************************************************!)

model "B-2 Flow shop"
 uses "mmxprs"
 
 declarations   
  NM = 3                               ! Number of machines
  NJ = 6                               ! Number of jobs
  MACH = 1..NM
  RANKS = 1..NJ
  JOBS = 1..NJ

  DUR: array(MACH,JOBS) of integer     ! Durations of jobs on machines

  rank: array(JOBS,RANKS) of mpvar     ! 1 if job j has rank k, 0 otherwise
  empty: array(MACH,1..NJ-1) of mpvar  ! Space between jobs of ranks k and k+1
  wtime: array(1..NM-1,RANKS) of mpvar ! Waiting time between machines m
                                       ! and m+1 for job of rank k
  start: array(MACH,RANKS) of mpvar    ! Start of job rank k on machine m 
                                       ! (optional)
 end-declarations

 initializations from 'b2flowshop.dat'
  DUR
 end-initializations

! Objective: total waiting time (= time before first job + times between 
! jobs) on the last machine
 TotWait:= sum(m in 1..NM-1,j in JOBS) (DUR(m,j)*rank(j,1)) +
           sum(k in 1..NJ-1) empty(NM,k)

! Every position gets a job
 forall(k in RANKS) sum(j in JOBS) rank(j,k) = 1

! Every job is assigned a rank
 forall(j in JOBS) sum(k in RANKS) rank(j,k) = 1

! Relations between the end of job rank k on machine m and start of job on 
! machine m+1
 forall(m in 1..NM-1,k in 1..NJ-1)
  empty(m,k) + sum(j in JOBS) DUR(m,j)*rank(j,k+1) + wtime(m,k+1) =
   wtime(m,k) + sum(j in JOBS) DUR(m+1,j)*rank(j,k) + empty(m+1,k)

! Calculation of start times (to facilitate the interpretation of results)
 forall(m in MACH, k in RANKS) 
  start(m,k) = sum(u in 1..m-1,j in JOBS) DUR(u,j)*rank(j,1) +
               sum(p in 1..k-1,j in JOBS) DUR(m,j)*rank(j,p) + 
               sum(p in 1..k-1) empty(m,p)

! First machine has no idle times
 forall(k in 1..NJ-1) empty(1,k) = 0

! First job has no waiting times
 forall(m in 1..NM-1) wtime(m,1) = 0

 forall(j in JOBS, k in RANKS) rank(j,k) is_binary  

(! Alternative formulations using SOS-1: 
 forall(j in JOBS) sum(k in RANKS) k*rank(j,k) is_sos1 
 forall(k in RANKS) sum(j in JOBS) j*rank(j,k) is_sos1 
!)

! Solve the problem
 minimize(TotWait)

! Solution printing
 writeln("Total waiting time for last machine: ", getobjval)
 write(strfmt("Item",-11))
  forall(k in RANKS) write(strfmt(getsol(sum(j in JOBS) j*rank(j,k)),3))
 writeln 
 forall(m in MACH) do
  write("Machine ", m, ": ")
  forall(k in RANKS) write(strfmt(start(m,k).sol,3))
  writeln
 end-do 

end-model 

b3jobshop.mos
(!******************************************************
   Mosel Example Problems
   ======================

   file b3jobshop.mos
   ``````````````````
   Job shop production planning.

   Three types of wallpaper pass through three machines in
   different orders depending on the design. Processing times
   differ based on surface and design. What order should the
   paper be scheduled so that the production is completed as soon
   as possible.

   Let 'JOBS' represent a printing job for one paper. In total,
   there are 8 jobs (2 for paper 1, 3 for paper 2, 3 for paper 3).
   Conjunctive constraints represent the precedence between jobs.
   Disjunctive constraints show that a machine can only have one
   job at a time. Note this problem introduces dynamic arrays and
   a range index. 'range' indicates an unknown index set that
   are consecutive integers. Dynamic arrays are used here for
   arrays with very few entries defined or of a priori unknown size. 

   (c) 2008-2022 Fair Isaac Corporation
       author: S. Heipcke, Mar. 2002, rev. Nov. 2017
*******************************************************!)

model "B-3 Job shop"
 uses "mmxprs"
 
 declarations                          
  JOBS=1..8                           ! Set of jobs (operations)

  DUR: array(JOBS) of integer         ! Durations of jobs on machines
  ARC: dynamic array(JOBS,JOBS) of integer   ! Precedence graph
  DISJ: dynamic array(JOBS,JOBS) of integer  ! Disjunctions between jobs
 
  start: array(JOBS) of mpvar         ! Start times of jobs
  finish: mpvar                       ! Schedule completion time
  y: dynamic array(range) of mpvar    ! Disjunction variables 
 end-declarations

 initializations from 'b3jobshop.dat'
  DUR ARC DISJ
 end-initializations
 
 BIGM:= sum(j in JOBS) DUR(j)         ! Some (sufficiently) large value

! Precedence constraints
 forall(j in JOBS) finish >= start(j)+DUR(j) 
 forall(i,j in JOBS | exists(ARC(i,j)) ) start(i)+DUR(i) <= start(j)

! Disjunctions
 d:=1
 forall(i,j in JOBS | i<j and exists(DISJ(i,j)) ) do
  create(y(d))
  y(d) is_binary
  start(i)+DUR(i) <= start(j)+BIGM*y(d)
  start(j)+DUR(j) <= start(i)+BIGM*(1-y(d))
  d+=1
 end-do

! Bound on latest completion time 
 finish <= BIGM

! Solve the problem: minimize latest completion time
 minimize(finish)

! Solution printing
 writeln("Total completion time: ", getobjval)
 forall(j in JOBS)
  writeln(j, ": ", getsol(start(j)), "-", getsol(start(j))+DUR(j))

end-model 

b3jobshop2.mos
(!******************************************************
   Mosel Example Problems
   ======================

   file b3jobshop2.mos
   ``````````````````
   Job shop production planning, 
   second, generic formulation.
   
   Three types of wallpaper pass through three machines in
   different orders depending on the design. Processing times
   differ based on surface and design. What order should the
   paper be scheduled so that the order is completed as soon
   as possible.
   
   This second model formulation uses double indices so that
   'start' is now defined by machine AND job. Duration and 
   sequence arrays are also expanded to machine and job.
   
   (c) 2008-2022 Fair Isaac Corporation
       author: S. Heipcke, Mar. 2002, rev. Mar. 2022
*******************************************************!)

model "B-3 Job shop (2)"
 uses "mmxprs", "mmsystem"
 
 declarations   
  JOBS: range                         ! Set of jobs (wall paper types)
  MACH: range                         ! Set of machines (colors)

  DUR: array(MACH,JOBS) of integer    ! Durations per machine and paper
  NUMT: array(JOBS) of integer        ! Number of tasks per job
  SEQ: array(JOBS,MACH) of integer    ! Machine sequence per job
  NUMD: array(MACH) of integer        ! No. of jobs (disjunctions) per machine
  DISJ: array(MACH,JOBS) of integer   ! List of jobs per machine
 
  start: dynamic array(MACH,JOBS) of mpvar  ! Start times of tasks
  finish: mpvar                       ! Schedule completion time
  y: dynamic array(range) of mpvar    ! Disjunction variables 
 end-declarations

 initializations from 'b3jobshop2.dat'
  DUR NUMT SEQ NUMD DISJ
 end-initializations

 forall(m in MACH, j in JOBS | DUR(m,j)>0 ) create(start(m,j))
 
 BIGM:=sum(m in MACH, j in JOBS) DUR(m,j)  ! Some (sufficiently) large value

! Precedence constraints
 forall(j in JOBS) finish >= start(SEQ(j,NUMT(j)),j) + DUR(SEQ(j,NUMT(j)),j)
 forall(j in JOBS, m in 1..NUMT(j)-1) 
  start(SEQ(j,m),j)+DUR(SEQ(j,m),j) <= start(SEQ(j,m+1),j)

! Disjunctions
 d:=1
 forall(m in MACH, i,j in 1..NUMD(m) | i<j) do
  create(y(d))
  y(d) is_binary
  start(m,DISJ(m,i))+DUR(m,DISJ(m,i)) <= start(m,DISJ(m,j))+BIGM*y(d)
  start(m,DISJ(m,j))+DUR(m,DISJ(m,j)) <= start(m,DISJ(m,i))+BIGM*(1-y(d))
  d+=1
 end-do

! Bound on latest completion time 
 finish <= BIGM

! Solve the problem: minimize latest completion time
 minimize(finish)

! Solution printing
 declarations
  COLOR: array(MACH) of string         ! Colors printed by the machines
 end-declarations

 initializations from 'b3jobshop2.dat'
  COLOR
 end-initializations

 writeln("Total completion time: ", getobjval)
 write("     ")
 forall(j in JOBS) write(strfmt(j,6))
 writeln
 forall(m in MACH) do
  write(strfmt(COLOR(m),-7))
  forall(j in JOBS)
   if(DUR(m,j)>0) then
    write(formattext("%3g-%g", start(m,j).sol, start(m,j).sol+DUR(m,j)))
   else
    write(" "*6)
   end-if 
  writeln
 end-do

end-model 

b3jobshop3.mos
(!******************************************************
   Mosel Example Problems
   ======================

   file b3jobshop3.mos
   ```````````````````
   Job shop production planning, 
   second, generic formulation.
   - Set/list version -
   
   Three types of wallpaper pass through three machines in
   different orders depending on the design. Processing times
   differ based on surface and design. What order should the
   paper be scheduled so that the order is completed as soon
   as possible.
   
   This second model formulation uses double indices so that
   'start' is now defined by machine AND job. The duration 
   array is also expanded to machine and job. The job sequence
   per machine is represented by an 'array of list' and the 
   set of disjunctive jobs per machine as an 'array of set'
   data structure.
   
   (c) 2008-2022 Fair Isaac Corporation
       author: S. Heipcke, Aug. 2006, rev. Mar. 2022
*******************************************************!)

model "B-3 Job shop (3)"
 uses "mmxprs"

 declarations   
  JOBS: range                         ! Set of jobs (wall paper types)
  MACH: range                         ! Set of machines (colors)

  DUR: array(MACH,JOBS) of integer    ! Durations per machine and paper
  SEQ: array(JOBS) of list of integer ! Machine sequence per job
  DISJ: array(MACH) of set of integer ! Sets of jobs per machine
 
  start: array(MACH,JOBS) of mpvar    ! Start times of tasks
  finish: mpvar                       ! Schedule completion time
  y: array(range) of mpvar            ! Disjunction variables 
 end-declarations

 initializations from 'b3jobshop3.dat'
  DUR SEQ
 end-initializations

 forall(m in MACH, j in JOBS | DUR(m,j)>0 ) create(start(m,j))
 
 BIGM:=sum(m in MACH, j in JOBS) DUR(m,j)  ! Some (sufficiently) large value

! Precedence constraints
 forall(j in JOBS, jlast=SEQ(j).last) finish >= start(jlast,j) + DUR(jlast,j)
 forall(j in JOBS) do
  pred:= SEQ(j).first     ! Same as: SEQ(j)(1)
  forall(m in gettail(SEQ(j),-1)) do 
   start(pred,j)+DUR(pred,j) <= start(m,j)
   pred:=m
  end-do
 end-do

! Disjunctions
 forall(m in MACH) DISJ(m):= union(j in JOBS | findfirst(SEQ(j),m)<>0) {j}
 d:=1
 forall(m in MACH, i,j in DISJ(m) | i<j) do
  create(y(d))
  y(d) is_binary
  start(m,i) + DUR(m,i) <= start(m,j) + BIGM*y(d)
  start(m,j) + DUR(m,j) <= start(m,i) + BIGM*(1-y(d))
  d+=1
 end-do

! Bound on latest completion time 
 finish <= BIGM

! Solve the problem: minimize latest completion time
 minimize(finish)

! Solution printing
 declarations
  COLOR: array(MACH) of string         ! Colors printed by the machines
 end-declarations

 initializations from 'b3jobshop3.dat'
  COLOR
 end-initializations

 writeln("Total completion time: ", getobjval)
 write("     ")
 forall(j in JOBS) write(strfmt(j,6))
 writeln
 forall(m in MACH) do
  write(strfmt(COLOR(m),-7))
  forall(j in JOBS)
   if(DUR(m,j)>0) then
    write(strfmt(getsol(start(m,j)),3), "-", getsol(start(m,j))+DUR(m,j))
   else
    write(strfmt(" ",6))
   end-if 
  writeln
 end-do
 
end-model 

b4seq.mos
(!******************************************************
   Mosel Example Problems
   ======================

   file b4seq.mos
   ``````````````
   Sequencing jobs on a bottleneck machine

   This problem provides a simple model for scheduling tasks
   on a single machine (a critical machine or bottleneck).
   Three objectives are solved for - minimizing the total
   schedule duration 'makespan', the average completion time,
   or the total lateness.
   
   A parameter is passed to the print solution procedure to
   indicate which objective was solved and print results
   accordingly, applying format settings locally within
   the subroutine.

   (c) 2008-2022 Fair Isaac Corporation
       author: S. Heipcke, Mar. 2002, rev. Mar. 2022
*******************************************************!)

model "B-4 Sequencing"
 uses "mmxprs"

 forward procedure printsol(obj:integer)
 
 declarations   
  NJ = 7                          ! Number of jobs
  JOBS=1..NJ

  REL: array(JOBS) of integer     ! Release dates of jobs
  DUR: array(JOBS) of integer     ! Durations of jobs
  DUE: array(JOBS) of integer     ! Due dates of jobs

  rank: array(JOBS,JOBS) of mpvar ! =1 if job j at position k
  start: array(JOBS) of mpvar     ! Start time of job at position k
  comp: array(JOBS) of mpvar      ! Completion time of job at position k
  late: array(JOBS) of mpvar      ! Lateness of job at position k
  finish: mpvar                   ! Completion time of the entire schedule
 end-declarations
 
 initializations from 'b4seq.dat'
  DUR REL DUE
 end-initializations

! One job per position
  forall(k in JOBS) sum(j in JOBS) rank(j,k) = 1

! One position per job 
  forall(j in JOBS) sum(k in JOBS) rank(j,k) = 1

! Sequence of jobs
  forall(k in 1..NJ-1)
   start(k+1) >= start(k) + sum(j in JOBS) DUR(j)*rank(j,k)

! Start times
  forall(k in JOBS) start(k) >= sum(j in JOBS) REL(j)*rank(j,k)

! Completion times
  forall(k in JOBS) comp(k) = start(k) + sum(j in JOBS) DUR(j)*rank(j,k)

 forall(j,k in JOBS) rank(j,k) is_binary 
 
! Objective function 1: minimize latest completion time
 forall(k in JOBS) finish >= comp(k)
 minimize(finish)
 printsol(1)

! Objective function 2: minimize average completion time
 minimize(sum(k in JOBS) comp(k))
 printsol(2)

! Objective function 3: minimize total tardiness
 forall(k in JOBS) late(k) >= comp(k) - sum(j in JOBS) DUE(j)*rank(j,k) 
 minimize(sum(k in JOBS) late(k))
 printsol(3)

!-----------------------------------------------------------------

! Solution printing
 procedure printsol(obj:integer)
  writeln("Objective ", obj, ": ", getobjval,
          if(obj>1, "  completion time: " + getsol(finish), "") ,
          if(obj<>2, "  average: " + getsol(sum(k in JOBS) comp(k)), ""),
          if(obj<>3, "  lateness: " + getsol(sum(k in JOBS) late(k)), ""))
  write("\t")
  localsetparam("REALFMT","%4g")  ! Reserve 4 characters for display of reals
  forall(k in JOBS) write(getsol(sum(j in JOBS) j*rank(j,k)))
  write("\nRel\t")
  forall(k in JOBS) write(getsol(sum(j in JOBS) REL(j)*rank(j,k)))
  write("\nDur\t")
  forall(k in JOBS) write(getsol(sum(j in JOBS) DUR(j)*rank(j,k)))
  write("\nStart\t")
  forall(k in JOBS) write(getsol(start(k)))
  write("\nEnd\t")
  forall(k in JOBS) write(getsol(comp(k)))
  write("\nDue\t")
  forall(k in JOBS) write(getsol(sum(j in JOBS) DUE(j)*rank(j,k)))
  if(obj=3) then
   write("\nLate\t")
   forall(k in JOBS) write(getsol(late(k)))
  end-if
  writeln
 end-procedure
 
end-model 
 

b5paint.mos
(!******************************************************
   Mosel Example Problems
   ======================

   file b5paint.mos
   ````````````````
   Planning of paint production

   5 batches of paint needs produced each week. The blender
   needs cleaned between each batch. Blending and cleaning
   times vary by color and paint type. What is the order of the 
   batches so that all 5 are completed in the quickest time?

   A new loop type ('repeat-until') is introduced to enumerate
   the batches in scheduled order. The function 'integer' 
   is used to transform the solution variables from real so 
   that the value is truncated and is displayed as an integer.
   
   (c) 2008-2022 Fair Isaac Corporation
       author: S. Heipcke, Mar. 2002, rev. Mar. 2022
*******************************************************!)

model "B-5 Paint production"
 uses "mmxprs", "mmsystem"

 declarations   
  NJ = 5                             ! Number of paint batches (=jobs)
  JOBS=1..NJ

  DUR: array(JOBS) of integer        ! Durations of jobs
  CLEAN: array(JOBS,JOBS) of integer ! Cleaning times between jobs

  succ: array(JOBS,JOBS) of mpvar    ! =1 if batch i is followed by batch j,
                                     ! =0 otherwise
  y: array(JOBS) of mpvar            ! Variables for excluding subtours
 end-declarations

 initializations from 'b5paint.dat'
  DUR CLEAN 
 end-initializations
 
! Objective: minimize the duration of a production cycle
 CycleTime:= sum(i,j in JOBS | i<>j) (DUR(i)+CLEAN(i,j))*succ(i,j)

! One successor and one predecessor per batch
 forall(i in JOBS) sum(j in JOBS | i<>j) succ(i,j) = 1
 forall(j in JOBS) sum(i in JOBS | i<>j) succ(i,j) = 1

! Exclude subtours
 forall(i in JOBS, j in 2..NJ | i<>j) y(j) >= y(i) + 1 - NJ * (1 - succ(i,j))

 forall(i,j in JOBS | i<>j) succ(i,j) is_binary
                                         
! Solve the problem
 minimize(CycleTime)
 
! Solution printing
 writeln("Minimum cycle time: ", getobjval)
 writeln("Sequence of batches:\nBatch Duration Cleaning")
 first:=1 
 repeat
  second:= round(sum(j in JOBS | first<>j) j*getsol(succ(first,j)) )
  writeln(formattext("  %g%8g%9g", first, DUR(first), CLEAN(first,second)))
  first:=second
 until (second=1)   

end-model

b6linebal.mos
(!******************************************************
   Mosel Example Problems
   ======================

   file b6linebal.mos
   ``````````````````
   Assembly line balancing
   
   An electronics factory has 4 workstations that can 
   produce amplifiers. Each amplifier has 12 production 
   steps. The manager would like to distribute these steps
   across the workstations to balance the workload and complete
   the amplifiers in the shortest possible time. Each step
   must be assigned a workstation and each station can only
   have one step at a time. Which steps should be assigned to
   each station to achieve the fastest amplifier production time?
   
   This mixed integer problem uses 'ARC' to define the relationship
   between steps and their predecessors. Binary variables are used
   to assign tasks to stations (machines).

   (c) 2008-2022 Fair Isaac Corporation
       author: S. Heipcke, Mar. 2002, rev. Mar. 2022
*******************************************************!)

model "B-6 Assembly line balancing"
 uses "mmxprs"

 declarations   
  MACH=1..4                             ! Set of workstations
  TASKS=1..12                           ! Set of tasks

  DUR: array(TASKS) of integer          ! Durations of tasks
  ARC: array(RA:range, 1..2) of integer ! Precedence relations between tasks

  process: array(TASKS,MACH) of mpvar   ! 1 if task on machine, 0 otherwise
  cycle: mpvar                          ! Duration of a production cycle
 end-declarations

 initializations from 'b6linebal.dat'
  DUR ARC 
 end-initializations

! One workstation per task 
 forall(i in TASKS) sum(m in MACH) process(i,m) = 1

! Sequence of tasks
 forall(a in RA) sum(m in MACH) m*process(ARC(a,1),m) <=
                  sum(m in MACH) m*process(ARC(a,2),m)

! Cycle time
 forall(m in MACH) sum(i in TASKS) DUR(i)*process(i,m) <= cycle

 forall(i in TASKS, m in MACH) process(i,m) is_binary

! Minimize the duration of a production cycle
 minimize(cycle)
 
! Solution printing
 writeln("Minimum cycle time: ", getobjval)
 forall(m in MACH) do
  write("Workstation ", m, ":")
  forall(i in TASKS | getsol(sum(k in MACH) k*process(i,k)) = m) write(" ", i) 
  writeln(" (duration: ", getsol(sum(i in TASKS) DUR(i)*process(i,m)),")")
 end-do  
 
end-model

© 2001-2024 Fair Isaac Corporation. All rights reserved. This documentation is the property of Fair Isaac Corporation (“FICO”). Receipt or possession of this documentation does not convey rights to disclose, reproduce, make derivative works, use, or allow others to use it except solely for internal evaluation purposes to determine whether to purchase a license to the software described in this documentation, or as otherwise set forth in a written software license agreement between you and FICO (or a FICO affiliate). Use of this documentation and the software described in it must conform strictly to the foregoing permitted uses, and no other use is permitted.