Initializing help system before first use

D. Loading and cutting problems


Description:

Problem name and type, features Difficulty Related examples
D‑1 Wagon load balancing: Nonpreemptive scheduling on parallel machines ****
heuristic solution requiring sorting algorithm, formulation of maximin objective; nested subroutines: function returning heuristic solution value and sorting procedure, ceil, getsize, if-then, break, exit, all loop types (forall-do, repeat-until, while-do), setparam, qsort, cutoff value, loading a MIP start solution
D‑2 Barge loading: Knapsack problem ** burglar1.mos, knapsack_graph.mos
incremental problem definition with 3 different objectives, procedure for solution printing
D‑3 Tank loading: Loading problem ***
2 objectives; data preprocessing, as, dynamic creation of variables, procedure for solution printing, if-then-else
D‑4 Backing up files: Bin-packing problem ** binpacking_graph.mos
2 versions of mathematical model, symmetry breaking; data preprocessing, ceil, range
D‑5 Cutting sheet metal: Covering problem * g6transmit.mos, j2bigbro.mos
D‑6 Cutting steel bars for desk legs: Cutting-stock problem ** cutstock_graph.mos
set operation(s) on range sets, set of integer (data as set contents)


File(s): d1wagon.mos (Mar. 2002), d1wagon2.mos (Sep. 2007), d2ship.mos (Mar. 2002), d3tanks.mos (Mar. 2002), d4backup.mos (Mar. 2002), d5cutsh.mos (Mar. 2002), d6cutbar.mos (Mar. 2002)
Data file(s): d1wagon.dat, d2ship.dat, d3tanks.dat, d4backup.dat, d5cutsh.dat, d6cutbar.dat

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

   file d1wagon.mos
   ````````````````
   Load balancing of train wagons
   
   Sixteen boxes must be loaded on three railway wagons.
   Each wagon has a weight limit of 100 quintals. Which wagon
   should each box be assigned so that the heaviest wagon load
   is minimized. 
   
   A heuristic solution can be found by distributing all boxes
   to wagons by assigning the heaviest box to the least loaded
   wagon. This requires the boxes to be in order of decreasing
   weight. The sorting procedure introduces 'getsize', and nested
   'repeat-until', 'forall-do', and 'while' loops with break 
   condition. The implementation of the heuristic also introduces 
   the subroutine type 'function' to return the highest wagon load
   weight.

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

model "D-1 Wagon load balancing"
 uses "mmxprs"

 forward function solveheur:real
 forward procedure shellsort(A:array(range) of integer, 
                             I:array(range) of integer)
 
 declarations   
  BOXES = 1..16                        ! Set of boxes
  WAGONS = 1..3                        ! Set of wagons

  WEIGHT: array(BOXES) of integer      ! Box weights
  WMAX: integer                        ! Weight limit per wagon

  ifload: array(BOXES,WAGONS) of mpvar ! 1 if box loaded on wagon, 0 otherwise
  maxweight: mpvar                     ! Weight of the heaviest wagon load
 end-declarations

 initializations from 'd1wagon.dat'
  WEIGHT WMAX
 end-initializations

! Solve the problem heuristically and terminate the program if the
! heuristic solution is good enough
 if solveheur<=WMAX then
  writeln("Heuristic solution fits capacity limits")
  exit(0)
 end-if

! Every box into one wagon
 forall(b in BOXES) sum(w in WAGONS) ifload(b,w) = 1
 
! Limit the weight loaded into every wagon 
 forall(w in WAGONS) sum(b in BOXES) WEIGHT(b)*ifload(b,w) <= maxweight
 
! Bounds on maximum weight
 maxweight <= WMAX
 maxweight >= ceil((sum(b in BOXES) WEIGHT(b))/3)

 forall(b in BOXES,w in WAGONS) ifload(b,w) is_binary

! Alternative to lower bound on maxweight: adapt the optimizer cutoff value 
! setparam("XPRS_MIPADDCUTOFF",-0.99999)

! Uncomment the following line to see the optimizer log
 setparam("XPRS_VERBOSE",true) 

! Minimize the heaviest load
 minimize(maxweight)                    ! Start optimization
 
! Solution printing
 writeln("Optimal solution:\n Max weight: ", getobjval)
 forall(w in WAGONS) do
  write(" ", w, ":")
  forall(b in BOXES | ifload(b,w).sol=1) write(" ", b)
  writeln(" (total weight: ", getsol(sum(b in BOXES) WEIGHT(b)*ifload(b,w)), ")")
 end-do

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

(! LPT (Longest processing time) heuristic: 
   One at a time place the heaviest unassigned box onto the wagon with 
   the least load
!)
   
 function solveheur:real
  declarations
   ORDERW: array(BOXES) of integer      ! Box indices in decreasing weight order
   Load: array(WAGONS,range) of integer ! Boxes loaded onto the wagons 
   CurWeight: array(WAGONS) of integer  ! Current weight of wagon loads 
   CurNum: array(WAGONS) of integer     ! Current number of boxes per wagon
  end-declarations

 ! Copy the box indices into array ORDERW and sort them in decreasing 
 ! order of box weights (the sorted indices are returned in array ORDERW) 
  forall(b in BOXES) ORDERW(b):=b
  shellsort(WEIGHT,ORDERW)

 ! Distribute the loads to the wagons using the LPT heuristic 
  forall(b in BOXES) do
   v:=1                                 ! Find wagon with the smallest load
   forall(w in WAGONS) v:=if(CurWeight(v)<CurWeight(w), v, w)     
   CurNum(v)+=1                         ! Increase the counter of boxes on v
   Load(v,CurNum(v)):=ORDERW(b)         ! Add box to the wagon
   CurWeight(v)+=WEIGHT(ORDERW(b))      ! Update current weight of the wagon
  end-do
 
  returned:= max(w in WAGONS) CurWeight(w)  ! Return the solution value

 ! Solution printing
  writeln("Heuristic solution:\n Max weight: ", returned)
  forall(w in WAGONS) do
   write(" ", w, ":")
   forall(b in 1..CurNum(w)) write(" ", Load(w,b))
   writeln(" (total weight: ", CurWeight(w), ")")
  end-do

 end-function

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

(! Sort an array in decreasing order using a Shell sort method:
   * First sort, by straight insertion, small groups of numbers. 
   * Next, combine several small groups and sort them (possibly 
     repeat this step). 
   * Finally, sort the whole list of numbers.

   The spacings between the numbers of groups sorted during each 
   pass through the data are called the increments. A good choice
   is the sequence which can be generated by the recurrence
   i(1)=1, i(k+1)=3i(k)+1, k=1,2,...
   
   The implementation assumes that the indices of the array to sort
   have the values 1,...,N. The array to be sorted (first argument)
   remains unchanged, instead, we reorder the array of indices (second 
   argument).
!)   

 procedure shellsort(A:array(range) of integer, I:array(range) of integer)
  N:=getsize(I)
  inc:=1                                ! Determine the starting increment
  repeat                         
   inc:=3*inc+1
  until (inc>N)  
 
  repeat                                ! Loop over the partial sorts
   inc:=inc div 3
   forall(i in inc+1..N) do             ! Outer loop of straight insertion
    v:=I(i)
    j:=i
    while (A(I(j-inc))<A(v)) do         ! Inner loop of straight insertion
     I(j):=I(j-inc)
     j -= inc
     if j<=inc then break; end-if
    end-do
    I(j):= v     
   end-do  
  until (inc<=1)
 end-procedure

end-model

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

   file d1wagon2.mos
   `````````````````
   Load balancing of train wagons
   (second version, using heuristic solution as 
    start solution for MIP via 'addmipsol')
    
   Sixteen boxes must be loaded on three railway wagons.
   Each wagon has a weight limit of 100 quintals. Which wagon
   should each box be assigned so that the heaviest wagon load
   is minimized.
   
   The heuristic solution is used as the starting point for
   MIP. Instead of a custom sorting procedure, the heuristic
   uses a form of 'qsort' which sorts the index array of an array.
 
   (c) 2008-2022 Fair Isaac Corporation
       author: S. Heipcke, Sep. 2007, rev. Mar. 2022
*******************************************************!)

model "D-1 Wagon load balancing (2)"
 uses "mmxprs", "mmsystem"

 forward function solveheur:real
 forward procedure solnotify(id:string, status:integer)
 
 declarations   
  BOXES = 1..16                        ! Set of boxes
  WAGONS = 1..3                        ! Set of wagons

  WEIGHT: array(BOXES) of integer      ! Box weights
  WMAX: integer                        ! Weight limit per wagon

  ifload: array(BOXES,WAGONS) of mpvar ! 1 if box loaded on wagon, 0 otherwise
  maxweight: mpvar                     ! Weight of the heaviest wagon load
  MaxWeight: linctr                    ! Objective function

  HeurSol: array(BOXES) of integer     ! Heuristic solution
  AllSol: array(mpvar) of real         ! Start solution for MIP
 end-declarations

 initializations from 'd1wagon.dat'
  WEIGHT WMAX
 end-initializations

! Solve the problem heuristically and terminate the program if the
! heuristic solution is good enough, otherwise, load heuristic solution
! as start solution into the Optimizer
 if solveheur<=WMAX then
  writeln("Heuristic solution fits capacity limits")
  exit(0)
 end-if

! Every box into one wagon
 forall(b in BOXES) sum(w in WAGONS) ifload(b,w) = 1
 
! Limit the weight loaded into every wagon 
 forall(w in WAGONS) sum(b in BOXES) WEIGHT(b)*ifload(b,w) <= maxweight
 
! Lower bound on maximum weight
 maxweight >= ceil((sum(b in BOXES) WEIGHT(b))/3)

 forall(b in BOXES,w in WAGONS) ifload(b,w) is_binary

! Alternative to lower bound on maxweight: adapt the optimizer cutoff value 
! setparam("XPRS_MIPADDCUTOFF",-0.99999)

! Uncomment the following line to see the optimizer log
! setparam("XPRS_VERBOSE",true) 

! Set the solution values for all discrete variables that are non-zero
 forall(b in BOXES) AllSol(ifload(b,HeurSol(b))):= 1

! Minimize the heaviest load
 MaxWeight:= maxweight                  ! Objective must be a constraint
                                        ! otherwise 'minimize' reloads problem
 loadprob(MaxWeight)                    ! Load problem into the Optimizer
 addmipsol("HeurSol", AllSol)           ! Load the heuristic solution

 setcallback(XPRS_CB_SOLNOTIFY,->solnotify)  ! Reporting use of user solution

! Re-inforce use of user solution in local search heuristics 
 setparam("XPRS_USERSOLHEURISTIC",3)

 minimize(MaxWeight)                    ! Start optimization
 
! Solution printing
 writeln("Optimal solution:\n Max weight: ", getobjval)
 forall(w in WAGONS) do
  write(" ", w, ":")
  forall(b in BOXES | ifload(b,w).sol=1) write(" ", b)
  writeln(" (total weight: ", getsol(sum(b in BOXES) WEIGHT(b)*ifload(b,w)), ")")
 end-do

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

(! LPT (Longest processing time) heuristic: 
   One at a time place the heaviest unassigned box onto the wagon with 
   the least load
!)
   
 function solveheur:real
  declarations
   ORDERW: array(BOXES) of integer      ! Box indices in decreasing weight order
   Load: array(WAGONS,range) of integer ! Boxes loaded onto the wagons 
   CurWeight: array(WAGONS) of integer  ! Current weight of wagon loads 
   CurNum: array(WAGONS) of integer     ! Current number of boxes per wagon
  end-declarations

 ! Copy the box indices into array ORDERW and sort them in decreasing 
 ! order of box weights (the sorted indices are returned in array ORDERW) 
  forall(b in BOXES) ORDERW(b):=b
  qsort(SYS_DOWN, WEIGHT, ORDERW)

 ! Distribute the loads to the wagons using the LPT heuristic 
  forall(b in BOXES) do
   v:=1                                 ! Find wagon with the smallest load
   forall(w in WAGONS) v:=if(CurWeight(v)<CurWeight(w), v, w)     
   CurNum(v)+=1                         ! Increase the counter of boxes on v
   Load(v,CurNum(v)):=ORDERW(b)         ! Add box to the wagon
   CurWeight(v)+=WEIGHT(ORDERW(b))      ! Update current weight of the wagon
  end-do
 
  returned:= max(w in WAGONS) CurWeight(w)  ! Return the solution value

 ! Solution printing
  writeln("Heuristic solution:\n Max weight: ", returned)
  forall(w in WAGONS) do
   write(" ", w, ":")
   forall(b in 1..CurNum(w)) write(" ", Load(w,b))
   writeln(" (total weight: ", CurWeight(w), ")")
  end-do

 ! Save the heuristic solution
  forall(w in WAGONS,b in 1..CurNum(w)) HeurSol(Load(w,b)):= w

 end-function

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

(! Optimizer callback function: 
   Report on the use of the user solution (optional logging function)
!)

 procedure solnotify(id:string, status:integer)
  writeln("Optimiser loaded solution '", id, "' status=", status)
 end-procedure

end-model

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

   file d2ship.mos
   ```````````````
   Choice of wheat load for a ship
   
   A shipper has 7 clients that wish to ship wheat. Each has
   varying quantities of lots, size of lots, shipping price,
   and transport costs. How can the shipper maximize profit?
   
   Three incrementally defined problems are solved in series. 
   Each introduces a new constraint while still maximizing profit.
   Procedure "printsol" is used to print the different 
   solutions depending on which problem is solved.
      
   (c) 2008-2022 Fair Isaac Corporation
       author: S. Heipcke, Mar. 2002, rev. Mar. 2022
*******************************************************!)

model "D-2 Ship loading"
 uses "mmxprs"

 forward procedure printsol(num:integer)

 declarations   
  CLIENTS = 1..7                    ! Set of clients

  AVAIL: array(CLIENTS) of integer  ! Number of lots per client
  SIZE: array(CLIENTS) of integer   ! Lot sizes
  PRICE: array(CLIENTS) of integer  ! Prices charged to clients
  COST: array(CLIENTS) of integer   ! Cost per client
  PROF: array(CLIENTS) of integer   ! Profit per client
  CAP: integer                      ! Capacity of the ship
 
  loadqty: array(CLIENTS) of mpvar  ! Lots taken from clients
 end-declarations

 initializations from 'd2ship.dat'
  AVAIL SIZE PRICE COST CAP
 end-initializations

 forall(c in CLIENTS) PROF(c):= PRICE(c) - COST(c)*SIZE(c)

 Profit:= sum(c in CLIENTS) PROF(c)*loadqty(c)

! Limit on the capacity of the ship
 sum(c in CLIENTS) SIZE(c)*loadqty(c) <= CAP

! Problem 1: unlimited availability of lots at clients
 maximize(Profit)
 printsol(1)

! Problem 2: limits on availability of lots at clients
 forall(c in CLIENTS) loadqty(c) <= AVAIL(c)

 maximize(Profit)
 printsol(2)

! Problem 3: lots must be integer
 forall(c in CLIENTS) loadqty(c) is_integer

 maximize(Profit)
 printsol(3)
 
!-----------------------------------------------------------------

! Solution printing
 procedure printsol(num:integer)
  writeln("Problem ", num, ": profit: ", getobjval)
  forall(c in CLIENTS) 
   write( if(getsol(loadqty(c))>0 , " " + c + ":" + getsol(loadqty(c)), ""))
  writeln
 end-procedure
 
end-model

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

   file d3tanks.mos
   ````````````````
   Loading of liquid chemicals into tanks

   Five tanker ships filled with liquids must be unloaded
   into storage tanks. The 5 liquids must not be mixed.
   (1) How should the ships be unloaded to maximize the capacity
   of unused tanks? (2) How should they be unloaded to maximize
   the number of unused tanks?

   The storage tanks are defined as a range of consecutive  
   integers whereas the liquids are identified by their names. 
   Entries of the decision variable array 'load' are created
   dynamically depending on the initial configuration data. 
   This problem calls the custom 'printsol' procedure after 
   minimizing each objective.   

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

model "D-3 Tank loading"
 uses "mmxprs"

 forward procedure printsol

 declarations   
  TANKS: range                       ! Set of tanks
  LIQ: set of string                 ! Set of liquids

  CAP: array(TANKS) of integer       ! Tank capacities
  TINIT: array(TANKS) of string      ! Initial tank contents type
  QINIT: array(TANKS) of integer     ! Quantity of initial contents
  ARR: array(LIQ) of integer         ! Arriving quantities of chemicals
  REST: array(LIQ) of integer        ! Rest after filling part. filled tanks
 
  ifload: dynamic array(LIQ,TANKS) of mpvar  ! 1 if liquid loaded into tank, 
                                     ! 0 otherwise
 end-declarations

 initializations from 'd3tanks.dat'
  CAP ARR
  [TINIT, QINIT] as 'FILLED'
 end-initializations

 finalize(LIQ)

 forall(t in TANKS | QINIT(t)=0, l in LIQ) do
  create(ifload(l,t))
  ifload(l,t) is_binary
 end-do 

! Complete the initially partially filled tanks and calculate the remaining
! quantities of liquids
 forall(l in LIQ) 
  REST(l):= ARR(l) - sum(t in TANKS | TINIT(t)=l) (CAP(t)-QINIT(t))
 
! Objective 1: total tank capacity used
 TankUse:= sum(l in LIQ, t in TANKS) CAP(t)*ifload(l,t)

! Objective 2: number of tanks used
 TankNum:= sum(l in LIQ, t in TANKS) ifload(l,t)

! Do not mix different liquids
 forall(t in TANKS) sum(l in LIQ) ifload(l,t) <= 1

! Load the empty tanks within their capacity limits
 forall(l in LIQ) sum(t in TANKS) CAP(t)*ifload(l,t) >= REST(l)

! Solve the problem with objective 1
 minimize(TankUse)
 
! Solution printing
 printsol

! Solve the problem with objective 2
 minimize(TankNum)
 
! Solution printing
 printsol
  
!-----------------------------------------------------------------

! Solution printing
 procedure printsol
  writeln("Used capacity: ", getsol(TankUse) + 
                             sum(t in TANKS | QINIT(t)>0) CAP(t),
         " Capacity of empty tanks: ", sum(t in TANKS) CAP(t) - 
                                       getsol(TankUse) - 
                                       sum(t in TANKS | QINIT(t)>0) CAP(t))
  writeln("Number of tanks used: ", getsol(TankNum) + 
                                    sum(t in TANKS | QINIT(t)>0) 1) 
  forall(t in TANKS)
   if(QINIT(t)=0) then
    write(t, ": ")
    forall(l in LIQ) write( if(getsol(ifload(l,t))>0 , l, ""))
    writeln
   else
    writeln(t, ": ", TINIT(t))
   end-if
 end-procedure
    
end-model

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

   file d4backup.mos
   `````````````````
   Bin packing: backup of files onto external storage units
   
   You would like to backup your 16 files onto external storage 
   units ('disks') with 1.44Gb of capacity. How should the files 
   be distributed in order to minimize the number of disks used?  
   This is a simple bin-packing problem since each file can only
   be saved to one disk.

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

model "D-4 Bin packing"
 uses "mmxprs"

 declarations
  ND: integer                          ! Number of disks
  FILES = 1..16                        ! Set of files
  DISKS: range                         ! Set of disks

  CAP:  integer                        ! Disk size
  SIZE: array(FILES) of integer        ! Size of files to be saved
 end-declarations
 
 initializations from 'd4backup.dat'
  CAP SIZE
 end-initializations

! Provide a sufficiently large number of disks
 ND:= ceil((sum(f in FILES) SIZE(f))/CAP)
 DISKS:= 1..ND
 writeln("Calculated upper bound: ", ND)

 declarations  
  ifsave: array(FILES,DISKS) of mpvar  ! 1 if file saved on disk, 0 otherwise
  diskuse: mpvar                       ! Number of disks used
 end-declarations

! Limit the number of disks used
 forall(f in FILES) diskuse >= sum(d in DISKS) d*ifsave(f,d)

! Every file onto a single disk
 forall(f in FILES) sum(d in DISKS) ifsave(f,d) = 1

! Capacity limit of disks
 forall(d in DISKS) sum(f in FILES) SIZE(f)*ifsave(f,d) <= CAP

 forall(d in DISKS,f in FILES) ifsave(f,d) is_binary

! Minimize the total number of disks used
 minimize(diskuse)
 
! Solution printing
  writeln("Number of disks used: ", getobjval)
  forall(d in 1..integer(getobjval)) do
   write(d, ":")
   forall(f in FILES | getsol(ifsave(f,d))>0) write(" ",SIZE(f))
   writeln("  space used: ", getsol(sum(f in FILES) SIZE(f)*ifsave(f,d)))
  end-do
      
end-model

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

   file d5cutsh.mos
   ````````````````
   Cutting of sheet metal 
   (2-dimensional cutting patterns)
   
   A sheet metal shop cuts large pieces of sheet metal into
   4 smaller sizes. There are 16 possible patterns that a 
   large sheet can be cut into. How can the incoming order
   be met while using the smallest number of large sheets?
   
   This mathematical model (formulated as a covering problem)
   is very compact since the patterns have already been 
   pre-computed.

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

model "D-5 Sheet metal cutting"
 uses "mmxprs"

 declarations
  PATTERNS = 1..16                       ! Set of cutting patterns
  SIZES = 1..4                           ! Set of sheet sizes

  DEM: array(SIZES) of integer           ! Demands for the different sizes
  CUT: array(SIZES,PATTERNS) of integer  ! Cutting patterns
  
  use: array(PATTERNS) of mpvar          ! Use of cutting patterns
 end-declarations
 
 initializations from 'd5cutsh.dat'
  DEM CUT
 end-initializations

! Objective: total number of sheets used
 Sheets:= sum(p in PATTERNS) use(p)

! Satisfy demands
 forall(s in SIZES) sum(p in PATTERNS) CUT(s,p)*use(p) >= DEM(s)

 forall(p in PATTERNS) use(p) is_integer

! Solve the problem
 minimize(Sheets)
 
! Solution printing
  writeln("Total number of large sheets: ", getobjval)
  write("Cutting patterns used: ")
  forall(p in PATTERNS)
   write( if(getsol(use(p)) > 0 , " " + p + ":" + getsol(use(p)), "") )
  write("\nExemplaries of sheets sizes cut: ")
  forall(s in SIZES)
   write(s, ":", getsol(sum(p in PATTERNS) CUT(s,p)*use(p)), " ")
  writeln
      
end-model

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

   file d6cutbar.mos
   `````````````````
   Cutting of steel bars into school desk legs 
   (1-dimensional cutting patterns)

   A company produces school desks of various heights. The
   legs are all cut from steel bars of 1.5 or 2 meters. How
   should an order be produced to minimize the trim loss?

   Note that each length of steel bars has a unique set of
   patterns. The total set of patterns is the union of these
   two sets. This problem also uses a 'set of integer' which is
   more general than a 'range [of integer]'.

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

model "D-6 Cutting steel bars"
 uses "mmxprs"

 declarations
  PAT1 = 1..6; PAT2 = 7..12              ! Sets of cutting patterns
  PATTERNS = PAT1 + PAT2                 ! Set of all cutting patterns
  SIZES: set of integer                  ! Desk heights

  DEM: array(SIZES) of integer           ! Demands for the different heights
  CUT: array(PATTERNS,SIZES) of integer  ! Cutting patterns
  LEN: array(range) of integer           ! Lengths of original steel bars
  
  use: array(PATTERNS) of mpvar          ! Use of cutting patterns
 end-declarations
 
 initializations from 'd6cutbar.dat'
  DEM CUT LEN
 end-initializations

! Objective: total loss
 Loss:= sum(p in PAT1) LEN(1)*use(p) + sum(p in PAT2) LEN(2)*use(p) - 
         sum(s in SIZES) 4*DEM(s)*s

! Satisfy demands
 forall(s in SIZES) sum(p in PATTERNS) CUT(p,s)*use(p) >= 4*DEM(s)

 forall(p in PATTERNS) use(p) is_integer

! Solve the problem
 minimize(Loss)
 
! Solution printing
  writeln("Loss: ", getobjval, "cm")
  write("Short bars: ", getsol(sum(p in PAT1) use(p)))
  writeln(", long bars: ", getsol(sum(p in PAT2) use(p)))
  write("Cutting patterns used:")
  forall(p in PATTERNS)
   write( if(getsol(use(p)) > 0 , " " + p + ":" + getsol(use(p)), "") )
  write("\nNumbers of legs cut: ")
  forall(s in SIZES)
   write(s, ":", getsol(sum(p in PATTERNS) CUT(p,s)*use(p)), " ")
  writeln
      
end-model

© 2001-2025 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.