Initializing help system before first use

I. Timetabling and personnel planning


Description:

Problem name and type, features Difficulty Related examples
I‑1 Assigning personnel to machines: Assignment problem **** assignment_graph.mos, c6assign.mos
formulation of maximin objective; heuristic solution + 2 different problems (incremental definition) solved, working with sets, while-do, forall-do
I‑2 Scheduling nurses ***
2 problems, using mod to formulate cyclic schedules; forall-do, set of integer, getact
I‑3 Establishing a college timetable *** timetable_graph.mos
many specific constraints, tricky (pseudo) objective function
I‑4 Exam schedule **
symmetry breaking, no objective
I‑5 Production planning with personnel assignment ***
2 problems, defined incrementally with partial re-definition of constraints (named constraints), exists, create, dynamic array
I‑6 Planning the personnel at a construction site ** persplan_graph.mos
formulation of balance constraints using inline if


File(s): i1assign.mos (Mar. 2002), i2nurse.mos (Mar. 2002), i3school.mos (Mar. 2002), i4exam.mos (Mar. 2002), i5pplan.mos (Mar. 2002), i6build.mos (Mar. 2002)
Data file(s): i1assign.dat, i2nurse.dat, i3school.dat, i4exam.dat, i5pplan.dat, i6build.dat

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

   file i1assign.mos
   `````````````````
   Assigning workers to machines

   Given a set of operators and a set of machines, an operator
   must be assigned to each of the six machines in a workshop.
   The productivity (pieces per hour) of each operator and 
   each machine is given. What operator should be assigned 
   to each machine to maximize the total productivity if machines
   are running in parallel? What should the assignment be 
   if machines are working in series?

   For the parallel-machines problem version, a simple IP 
   model is implemented. For the machines-working-in-series, 
   since total productivity is defined by the bottleneck 
   (operator-machine assignment with lowest productivity), 
   a new variable is introduced to define a minmax problem. 
   A procedure to obtain a heuristic solution is also 
   implemented.

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

model "I-1 Personnel assignment"
 uses "mmxprs", "mmsystem"

 forward procedure parallelheur
 forward procedure printsol(txt1,txt2:text)

 declarations
  PERS = 1..6                        ! Personnel
  MACH = 1..6                        ! Machines
  OUTP: array(PERS,MACH) of integer  ! Productivity
 end-declarations

 initializations from 'i1assign.dat'
  OUTP
 end-initializations

! **** Heuristic solution for parallel assignment ****
 parallelheur
 
! **** Exact solution for parallel assignment ****

 declarations
  assign: array(PERS,MACH) of mpvar  ! 1 if person assigned to machine, 
                                     ! 0 otherwise
 end-declarations

! Objective: total productivity
 TotalProd:= sum(p in PERS, m in MACH) OUTP(p,m)*assign(p,m)

! One machine per person
  forall(p in PERS) sum(m in MACH) assign(p,m) = 1

! One person per machine
  forall(m in MACH) sum(p in PERS) assign(p,m) = 1

! Solve the problem
 maximize(TotalProd)
 printsol("Exact solution (parallel assignment)", "Total")

! **** Exact solution for serial machines ****

 declarations
  pmin: mpvar                        ! Minimum productivity
 end-declarations

! Calculate minimum productivity
 forall(p in PERS) sum(m in MACH) OUTP(p,m)*assign(p,m) >= pmin

 forall(p in PERS, m in MACH) assign(p,m) is_binary

! Solve the problem
 maximize(pmin)
 printsol("Exact solution (serial machines)", "Minimum")
 
!-----------------------------------------------------------------

! Heuristic solution for parallel assignment
 procedure parallelheur
  declarations
   ALLP, ALLM: set of integer        ! Copies of sets PERS and MACH
   HProd: integer                    ! Total productivity value
   pmax,omax,mmax: integer
  end-declarations
  writeln("Heuristic solution:")

 ! Copy the sets of workers and machines
  forall(p in PERS) ALLP+={p}
  forall(m in MACH) ALLM+={m}

 ! Assign workers to machines as long as there are unassigned persons
  while (ALLP<>{}) do
   pmax:=0; mmax:=0; omax:=0

 ! Find the highest productivity among the remaining workers and machines
   forall(p in ALLP, m in ALLM)
    if OUTP(p,m) > omax then
     omax:=OUTP(p,m)
     pmax:=p; mmax:=m
    end-if   

   HProd+=omax                       ! Add to total productivity
   ALLP-={pmax}; ALLM-={mmax}        ! Remove person and machine from sets
  
   writeln("  ", pmax, " operates machine ", mmax, " (", omax, ")")
  end-do

  writeln("  Total productivity: ", HProd)
 end-procedure

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

! Solution printing
 procedure printsol(txt1,txt2:text)
  writeln(txt1, ":")
  forall(p in PERS) do
   mp:=round(getsol(sum(m in MACH) m*assign(p,m)))
   writeln("  ", p, " operates machine ", mp, " (", OUTP(p,mp), ")")
  end-do 
  writeln("  ", txt2, " productivity: ", getobjval)
 end-procedure
 
end-model

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

   file i2nurse.mos
   ````````````````
   Work schedule for nurses
   
   We must determine the schedule for nurses in a hospital. 
   A working day is divided into twelve two-hour periods. 
   The personnel requirement for every period is given. 
   The number of working hours and break hours per day is 
   also known. How many nurses should be assigned to each 
   period to satisfy the personnel requirements and minimize 
   the total number of nurses? For a second problem, a 
   maximum number of total nurses is defined but nurses can
   work overtime. Determine the schedule of nurses minimizing
   the total number of nurses working overtime.

   The demand of a particular period can be covered with nurses
   who start working in such a period, and with nurses starting
   in some preceding periods based on the working hours and 
   breaks. A generic demand constraint is built using the 'mod'
   operator to formulate cyclic schedules. 
   For question 2, a new decision variable is introduced to model 
   overtime, so demand constraints are adjusted accordingly.

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

model "I-2 Scheduling nurses"
 uses "mmxprs"

 declarations
  NT = 12                        ! Number of time periods
  TIME = 0..NT-1
  WORK: set of integer           ! Nurses started in other time periods
                                 ! that are working during a period
  
  REQ: array(TIME) of integer    ! Required number of nurses per time period
  
  Period: array(TIME) of linctr  ! Constraints on personnel per period
  start: array(TIME) of mpvar    ! Nurses starting work in a period
 end-declarations

 initializations from 'i2nurse.dat'
  REQ
 end-initializations

 WORK:= {0, -1, -3, -4}

! Objective: total personnel required
 Total:= sum(t in TIME) start(t)

! Nurses working per time period
 forall(t in TIME) Period(t):= sum(i in WORK) start((t+i+NT) mod NT) >= REQ(t) 

 forall(t in TIME) start(t) is_integer

! Solve the problem
 minimize(Total)
 
! Solution printing
 writeln("Total personnel: ", getobjval)
 forall(t in TIME) 
  writeln(strfmt(t*2,2), ":00-",strfmt((t+1)*2,2), ":00 : starting: ", 
          getsol(start(t)),
          " total: ", getsol(sum(i in WORK) start((t+i+NT) mod NT)))

! **** Second problem: minimize overtime with given staff level ****

 declarations
  NUM: integer                   ! Available total staff
  overt: array(TIME) of mpvar    ! Nurses working overtime
 end-declarations

 initializations from 'i2nurse.dat'
  NUM
 end-initializations

! Objective: total overtime worked
 TotalOvert:= sum(t in TIME) overt(t)

! Nurses working per time period
 forall(t in TIME) 
  Period(t):= overt((t-5+NT) mod NT) + sum(i in WORK) start((t+i+NT) mod NT) >= 
              REQ(t) 

! Limit on total number of nurses  
 Total <= NUM

 forall(t in TIME) do
  overt(t) is_integer
  overt(t) <= start(t)
 end-do 

! Solve the problem
 minimize(TotalOvert)
 
! Solution printing
 writeln("\nPersonnel working overtime: ", getobjval)
 forall(t in TIME) 
  writeln(strfmt(t*2,2), ":00-",strfmt((t+1)*2,2), ":00 : starting: ", 
          getsol(start(t)), " total: ", getact(Period(t)), 
          " overtime: ", getsol(overt((t-5+NT) mod NT)))

end-model

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

   file i3school.mos
   `````````````````
   Determine a timetable for 2 classes

   A weekly timetable for two classes must be determined.
   The classes have the same teachers, except for mathematics
   and sport. The duration of a lesson, the slots to schedule
   courses, and specific requirements on days and slots to
   assign some courses are given. All students of a course must
   attend exactly the same courses. What teachers should be
   assigned to each class in each time slot?

   This IP model minimizes the number of 'holes' in the class
   timetables, formulated indirectly via the number of courses
   scheduled in the first or last time slots per day. Although 
   most of constraints are implemented in a generic way, some  
   specific requirements are implemented as explicit constraints.

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

model "I-3 School timetable"
 uses "mmxprs"

 declarations
  TEACHERS: set of string         ! Set of teachers
  CLASS = 1..2                    ! Set of classes
  NP = 4                          ! Number of time periods for courses
  ND = 5                          ! Days per week
  SLOTS=1..NP*ND                  ! Set of time slots for the entire week
  
  COURSE: array(TEACHERS,CLASS) of integer ! Lessons per teacher and class
 end-declarations

 initializations from 'i3school.dat'
  COURSE
 end-initializations

 declarations
  teach: array(TEACHERS,CLASS,SLOTS) of mpvar 
                                  ! teach(t,c,l) = 1 if teacher t gives a
                                  ! lesson to class c during time period l
 end-declarations

! Objective: number of "holes" in the class timetables
 Hole:= 
  sum(t in TEACHERS, c in CLASS, d in 0..ND-1) (teach(t,c,d*NP+1) + 
      teach(t,c,(d+1)*NP))

! Plan all courses
 forall(t in TEACHERS, c in CLASS) sum(l in SLOTS) teach(t,c,l) = COURSE(t,c)

! For every class, one course at a time
 forall(c in CLASS, l in SLOTS) sum(t in TEACHERS) teach(t,c,l) <= 1

! Teacher teaches one course at a time
 forall(t in TEACHERS, l in SLOTS) sum(c in CLASS) teach(t,c,l) <= 1

! Every subject only once per day
 forall(t in TEACHERS, c in CLASS, d in 0..ND-1) 
  sum(l in d*NP+1..(d+1)*NP) teach(t,c,l) <= 1
 
! Sport Thursday afternoon (slot 15)
 teach("Mr Muscle",1,15) = 1
 teach("Mrs Biceps",2,15) = 1
 
! No course during first period of Monday morning
 forall(t in TEACHERS, c in CLASS) teach(t,c,1) = 0

! No course by Mr Effofecks Monday morning 
 forall(l in 1..2) teach("Mr Effofecks",2,l) = 0
 
! No Biology on Wednesday
 forall(c in CLASS, l in 2*NP+1..3*NP) teach("Mrs Insulin",c,l) = 0 

 forall(t in TEACHERS, c in CLASS, l in SLOTS) teach(t,c,l) is_binary
 
! Solve the problem
 minimize(Hole)
 
! Solution printing
 declarations
  DAYS=1..ND
  NAMES: array(DAYS) of string
 end-declarations
 
 initializations from 'i3school.dat'
  NAMES
 end-initializations

 writeln("Courses at begin or end of day: ", getobjval)
 forall(c in CLASS) do
  writeln("Class ",c)
  forall(d in DAYS) do
   write(NAMES(d), ":  ")
   forall(l in (d-1)*NP+1..d*NP)
    if (getsol(sum(t in TEACHERS) teach(t,c,l))>0) then
     forall(t in TEACHERS | getsol(teach(t,c,l))>0) write(strfmt(t,-14))
    else
     write(strfmt("",14))
    end-if     
   writeln 
  end-do
 end-do 

end-model

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

   file i4exam.mos
   ```````````````
   Scheduling exams

   A university must schedule the exams of both mandatory 
   and optional modules for fourth-year students. The exam
   duration and available time slots are given, as well as 
   the incompatibilities between different exams that cannot
   be taken at the same time. No student can have more than
   one exam at a time. What exam should be scheduled at each
   time slot?

   The incompatibilities are modeled as a Boolean matrix to 
   define conditions over the IP model constraints. Since 
   no objective is stated in the problem description, this
   model basically finds a feasible solution by defining
   a constant value as objective function.
   
   (c) 2008 Fair Isaac Corporation
       author: S. Heipcke, Mar. 2002
*******************************************************!)

model "I-4 Scheduling exams"
 uses "mmxprs"

 declarations
  EXAM = {"DA","NA","C++","SE","PM","J","GMA","LP","MP","S","DSE"}
                                      ! Set of exams
  TIME = 1..8                         ! Set of time slots
  
  INCOMP: array(EXAM,EXAM) of integer ! Incompatibility between exams
  
  plan: array(EXAM,TIME) of mpvar     ! 1 if exam in a time slot, 0 otherwise
 end-declarations

 initializations from 'i4exam.dat'
  INCOMP
 end-initializations

! Schedule all exams
 forall(e in EXAM) sum(t in TIME) plan(e,t) = 1
 
! Respect incompatibilities
 forall(d,e in EXAM, t in TIME | d<e and INCOMP(d,e)=1) 
  plan(e,t) + plan(d,t) <= 1    

 forall(e in EXAM, t in TIME) plan(e,t) is_binary

! Breaking symmetries
(!
 plan("DA",1)=1
 plan("NA",2)=1
 plan("PM",3)=1
 plan("GMA",4)=1
 plan("S",5)=1
 plan("DSE",6)=1
!) 

! Solve the problem (no objective)
 minimize(0)
 
! Solution printing
 forall(e in EXAM) 
  writeln(strfmt(e+":",4) ," slot ", getsol(sum(t in TIME) t*plan(e,t)))

end-model

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

   file i5pplan.mos
   ````````````````
   Production planning with personnel assignment
  
   A company must plan the production for a set of products
   on different production lines. Unitary processing times 
   for each product at each line, production line capacities,
   and profit per product are provided. It is possible to 
   transfer working hours (up to a given maximum allowed) 
   between some production lines. What quantity of each 
   product should be produced to maximize total profit?
   
   The hours transferred between production lines are modeled as
   a decision variable which is defined as a dynamic array. Only
   when the data that indicates the allowable transfers is known 
   the transfer variables are created.

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

model "I-5 Production planning with personnel"
 uses "mmxprs"

 forward procedure printsol

 declarations
  PRODS = 1..4                        ! Set of products
  LINES = 1..5                        ! Set of production lines
  
  PROFIT: array(PRODS) of integer     ! Profit per product
  DUR: array(PRODS,LINES) of real     ! Duration of production per line
  CAP: array(LINES) of integer        ! Working hours available per line
  
  Load: array(LINES) of linctr        ! Workload constraints
  produce: array(PRODS) of mpvar      ! Quantity produced
 end-declarations

 initializations from 'i5pplan.dat'
  PROFIT DUR CAP
 end-initializations

! Objective: Total profit
 Profit:= sum(p in PRODS) PROFIT(p)*produce(p)
 
! Capacity constraints on lines
 forall(l in LINES) Load(l):=sum(p in PRODS) DUR(p,l)*produce(p) <= CAP(l)

! Solve the problem
 maximize(Profit)
 printsol 

! **** Allow transfer of working hours between lines ****

 declarations
  TRANSF: dynamic array(LINES,LINES) of integer ! 1 if transfer is allowed, 
                                                ! 0 otherwise
  TMAX: array(LINES) of integer         ! Maximum no. of hours to transfer

  hours: array(LINES) of mpvar          ! Initial working hours per line
  transfer: dynamic array(LINES,LINES) of mpvar ! Hours transferred
 end-declarations

 initializations from 'i5pplan.dat'
  TRANSF TMAX
 end-initializations

 forall(k,l in LINES | exists(TRANSF(k,l))) create(transfer(k,l))

! Re-define capacity constraints on lines
 forall(l in LINES) Load(l):=sum(p in PRODS) DUR(p,l)*produce(p) <= hours(l)

! Balance constraints
 forall(l in LINES)
  hours(l)  = CAP(l) + sum(k in LINES) transfer(k,l) -
                      sum(k in LINES) transfer(l,k) 

! Limit on transfer
 forall(l in LINES) sum(k in LINES) transfer(l,k) <= TMAX(l)

! Solve the problem
 maximize(Profit)
 writeln("Solution with transfer of working hours:")
 printsol
 writeln("Transfers:")
 forall(l,k in LINES | exists(TRANSF(l,k)) and getsol(transfer(l,k))>0) 
  writeln(" ", l, "->", k, ": ", getsol(transfer(l,k)))

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

! Solution printing
 procedure printsol
  localsetparam("realfmt","%-8g")
  writeln("Total profit: ", getobjval)
  forall(p in PRODS)
   writeln("Product ", p, ": ", getsol(produce(p)))
  forall(l  in LINES)
   writeln("Line ", l, ": ", getsol(sum(p in PRODS) DUR(p,l)*produce(p))) 
 end-procedure
 
end-model

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

   file i6build.mos
   ````````````````
   Personnel planning at a construction site

   A company must plan the number of construction workers 
   at a specific site for a planning horizon. Transfers 
   from other sites to the specific site are possible at 
   the beginning of each period with an associated cost. 
   Under and over staffing is possible with a related cost. 
   How many workers should be planned at each time period
   while minimizing the total cost?

   This IP formulation models the problem with five different
   set of variables to facilitate the understanding of the 
   mathematical model. The balance constraints (for the number
   of workers at the site at each time period) are grouped 
   into a single expression using the inline 'if'.

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

model "I-6 Construction site personnel"
 uses "mmxprs"

 declarations
  FIRST = 3; LAST = 8
  MONTHS = FIRST..LAST                 ! Set of time periods (months)
  
  CARR, CLEAVE: integer                ! Cost per arrival/departure
  COVER, CUNDER: integer               ! Cost of over-/understaffing
  NSTART, NFINAL: integer              ! No. of workers at begin/end of plan
  REQ: array(MONTHS) of integer        ! Requirement of workers per month
  
  onsite: array(MONTHS) of mpvar       ! Workers on site
  arrive,leave: array(MONTHS) of mpvar ! Workers arriving/leaving
  over,under: array(MONTHS) of mpvar   ! Over-/understaffing
 end-declarations

 initializations from 'i6build.dat'
  CARR CLEAVE COVER CUNDER NSTART NFINAL REQ
 end-initializations
 
! Objective: total cost
 Cost:= sum(m in MONTHS) (CARR*arrive(m) + CLEAVE*leave(m) +
                          COVER*over(m) + CUNDER*under(m))

! Satisfy monthly need of workers
 forall(m in MONTHS) onsite(m) - over(m) + under(m) = REQ(m) 

! Balances
 forall(m in MONTHS)
  onsite(m) = if(m>FIRST, onsite(m-1) - leave(m-1), NSTART) + arrive(m)
 NFINAL = onsite(LAST) - leave(LAST)
  
! Limits on departures, understaffing, arrivals; integrality constraints
 forall(m in MONTHS) do
  leave(m) <= 1/3*onsite(m)
  under(m) <= 1/4*onsite(m)
  arrive(m) <= 3
  arrive(m) is_integer; leave(m) is_integer; onsite(m) is_integer
  under(m) is_integer; over(m) is_integer  
 end-do
 
! Solve the problem
 minimize(Cost)

! Solution printing
 declarations
  NAMES: array(MONTHS) of string       ! Names of months
 end-declarations
 
 initializations from 'i6build.dat'
  NAMES
 end-initializations
 
 writeln("Total cost: ", getobjval)
 write("Month     ")
 forall(m in MONTHS) write(NAMES(m)," ") 
 setparam("realfmt","%4g")    ! Reserve 4 char.s for real number display
 write("\nOn site ")
 forall(m in MONTHS) write(getsol(onsite(m))) 
 write("\nArrive  ")
 forall(m in MONTHS) write(getsol(arrive(m))) 
 write("\nLeave   ")
 forall(m in MONTHS) write(getsol(leave(m))) 
 write("\nOverst. ")
 forall(m in MONTHS) write(getsol(over(m))) 
 write("\nUnderst.")
 forall(m in MONTHS) write(getsol(under(m)))
 writeln
 
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.