Initializing help system before first use

A. Mining and process industries


Description:

Problem name and type, features Difficulty Related examples
A‑1 Production of alloys: Blending problem
formulation of blending constraints; data with numerical indices, solution printout, if-then, getsol
* blending_graph.mos
A‑2 Animal food production: Blending problem
formulation of blending constraints; data with string indices, as, formatted solution printout, use of getsol with linear expressions, strfmt
* a1alloy.mos
A‑3 Refinery : Blending problem
formulation of blending constraints; sparse data with string indices, dynamic initialization, union of sets
** a2food.mos
A‑4 Cane sugar production : Minimum cost flow (in a bipartite graph)
mo ceil, is_binary, formattext
* e2minflow.mos, mincostflow_graph.mos
A‑5 Opencast mining: Minimum cost flow
encoding of arcs, solving LP-relaxation only, array of set
** a4sugar.mos
A‑6 Production of electricity: Dispatch problem
inline if, is_integer, looping over optimization problem solving
**


File(s): a1alloy.mos (Feb. 2002), a2food.mos (Feb. 2002), a3refine.mos (Feb. 2002), a4sugar.mos (Feb. 2002), a5mine.mos (Feb. 2002), a5mine2.mos (Jan. 2006), a6electr.mos (Mar. 2002), a6electrg.mos (Oct. 2004)
Data file(s): a1alloy.dat, a2food.dat, a3refine.dat, a4sugar.dat, a5mine.dat, a5mine2.dat, a6electr.dat

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

   file a1alloy.mos
   ````````````````
   Production of alloys   
   
   An order of steel must be met with a range of carbon, 
   copper, and manganese grades. Given the raw materials in
   stock, the objective is to determine the composition of
   the steel that minimizes the production cost.
   
   Simple linear programming blending problem formulation includes 
   data with numerical indices and introduction of if-then statement 
   for solution printout.

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

model "A-1 Production of Alloys"
 uses "mmxprs"
 
 declarations
  COMP = 1..3                    ! Components (chemical elements)
  RAW  = 1..7                    ! Raw materials (alloys)
  
  P: array(RAW,COMP) of real     ! Composition of raw materials (in percent)
  PMIN,PMAX: array(COMP) of real ! Min. & max. requirements for components
  AVAIL: array(RAW) of real      ! Raw material availabilities
  COST: array(RAW) of real       ! Raw material costs per tonne
  DEM: real                      ! Amount of steel to produce

  use: array(RAW) of mpvar       ! Quantity of raw mat. used
  produce: mpvar                 ! Quantity of steel produced  
 end-declarations
 
 initializations from 'a1alloy.dat'
  P PMIN PMAX AVAIL COST DEM
 end-initializations

! Objective function  
 Cost:= sum(r in RAW) COST(r)*use(r)

! Quantity of steel produced = sum of raw material used
 produce = sum(r in RAW) use(r)

! Guarantee min. and max. percentages of every chemical element
 forall(c in COMP) do
  sum(r in RAW) P(r,c)*use(r) >= PMIN(c)*produce
  sum(r in RAW) P(r,c)*use(r) <= PMAX(c)*produce
 end-do
 
! Use raw materials within their limit of availability
 forall(r in RAW) use(r) <= AVAIL(r)

! Satisfy the demand
 produce >= DEM

! Solve the problem
 minimize(Cost)

! Solution printing
 declarations
  NAMES: array(RAW) of string
 end-declarations
 
 initializations from 'a1alloy.dat'   ! Get the names of the alloys
  NAMES
 end-initializations

 writeln("Total cost: ", getobjval)
 writeln("Amount of steel produced: ", getsol(produce))
 writeln("Alloys used:")
 forall(r in RAW) 
  if(getsol(use(r))>0) then
   write(NAMES(r), ": ", getsol(use(r)),"  ")
  end-if  
 write("\nPercentages (C, Cu, Mn): ")   
 forall(c in COMP) 
  write( getsol(sum(r in RAW) P(r,c)*use(r))/getsol(produce), "%  ")
 writeln

end-model

a2food.mos
(!******************************************************
   Mosel Example Problems
   ======================
    
   file a2food.mos
   ```````````````
   Food production for farm animals
   
   Food must meet required content levels of nutritional 
   components (Proteins, Lipids, Fiber). Given the raw 
   materials available each day and daily demand to meet, 
   the objective is to determine how the Oat, Maize, 
   and Molasses should be blended to minimize the total cost.

   Simple linear programming blending problem formulation includes 
   data with string indices and string formatting for solution printout.

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

model "A-2 Animal Food Production"
 uses "mmxprs"
 
 declarations
  FOOD = 1..2                    ! Food types
  COMP = 1..3                    ! Nutritional components
  RAW  = {"oat", "maize", "molasses"}   ! Raw materials
  
  P: array(RAW,COMP) of real     ! Composition of raw materials (in percent)
  REQ: array(COMP) of real       ! Nutritional requirements
  AVAIL: array(RAW) of real      ! Raw material availabilities
  COST: array(RAW) of real       ! Raw material prices
  PCOST: array(set of string) of real  ! Cost of processing operations
  DEM: array(FOOD) of real       ! Demands for food types

  use: array(RAW,FOOD) of mpvar  ! Quantity of raw mat. used for a food type
  produce: array(FOOD) of mpvar  ! Quantity of food produced
 end-declarations

 initializations from 'a2food.dat'
  P REQ PCOST DEM
  [AVAIL, COST] as 'RAWMAT'
 end-initializations
 
! Objective function  
 Cost:= sum(r in RAW,f in FOOD) COST(r)*use(r,f) +
        sum(r in RAW,f in FOOD|r<>"molasses") PCOST("grinding")*use(r,f) +
        sum(r in RAW,f in FOOD) PCOST("blending")*use(r,f) +
        sum(r in RAW) PCOST("granulating")*use(r,1) +
        sum(r in RAW) PCOST("sieving")*use(r,2)

! Quantity of food produced corresponds to raw material used
 forall(f in FOOD) sum(r in RAW) use(r,f) = produce(f)

! Fulfill nutritional requirements
 forall(f in FOOD,c in 1..2) 
  sum(r in RAW) P(r,c)*use(r,f) >= REQ(c)*produce(f)
 forall(f in FOOD) sum(r in RAW) P(r,3)*use(r,f) <= REQ(3)*produce(f)

! Use raw materials within their limit of availability
 forall(r in RAW) sum(f in FOOD) use(r,f) <= AVAIL(r)

! Satisfy demands
 forall(f in FOOD) produce(f) >= DEM(f)

! Solve the problem
 minimize(Cost)

! Solution printing
 writeln("Total cost: ", getobjval)
 write("Food type"); forall(r in RAW) write(strfmt(r,9))
 writeln("  protein  lipid   fiber")
 forall(f in FOOD) do
  write(strfmt(f,-9))
  forall(r in RAW) write(strfmt(getsol(use(r,f)),9,2))     
  forall(c in COMP) write("   ", 
   strfmt(getsol(sum(r in RAW) P(r,c)*use(r,f))/getsol(produce(f)),3,2),"%")
  writeln
 end-do
 
end-model

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

   file a3refine.mos
   `````````````````
   Refinery planning
 
   A refinery produces butane, petrol, diesel oil, and heating oil 
   from two crudes. Four types of operations are necessary to 
   obtain these products: separation, conversion, upgrading, and 
   blending. Monthly demand must be met while certain levels of 
   octane value, vapor pressure, volatility, and sulfur content are 
   enforced by law. The objective is to minimize crude and production cost.

   A much more involved linear programming blending problem
   with two production stages that are related in complicated ways.  
   The implementation has sparse data with string indices that are 
   initialized dynamically from the input data file. A new set 
   'ALLPRODS' is defined as the union of several other sets.

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

model "A-3 Refinery planning"
 uses "mmxprs"
 
 declarations
  CRUDES: set of string                   ! Set of crudes
  ALLPRODS: set of string                 ! Intermediate and final products
  FINAL: set of string                    ! Final products
  IDIST: set of string                    ! Products obtained by distillation
  IREF: set of string                     ! Products obtained by reforming
  ICRACK: set of string                   ! Products obtained by cracking
  IPETROL: set of string                  ! Interm. products for petrol
  IDIESEL: set of string                  ! Interm. products for diesel
  IHO={"hogasoil", "hocrknaphtha", "hocrkgasoil"}  
                                          ! Interm. products for heating oil
  DEM: array(FINAL) of real               ! Min. production
  COST: array(set of string) of real      ! Production costs
  AVAIL: array(CRUDES) of real            ! Crude availability
  OCT, VAP, VOL: array(IPETROL) of real   ! Octane, vapor pressure, and 
                                          ! volatility values
  SULF: array(IDIESEL) of real            ! Sulfur contents
  DIST: array(CRUDES,IDIST) of real       ! Composition of crudes (in %)
  REF: array(IREF) of real                ! Results of reforming (in %)
  CRACK: array(ICRACK) of real            ! Results of cracking (in %)
 end-declarations

 initializations from 'a3refine.dat'
  DEM COST OCT VAP VOL SULF AVAIL DIST REF CRACK
 end-initializations

 ALLPRODS:= FINAL+IDIST+IREF+ICRACK+IPETROL+IHO+IDIESEL

 declarations
  use: array(CRUDES) of mpvar             ! Quantities used
  produce: array(ALLPRODS) of mpvar       ! Quantities produced
 end-declarations

! Objective function
 Cost:= sum(c in CRUDES) COST(c)*use(c) + sum(p in IDIST) COST(p)*produce(p)

! Relations intermediate products resulting of distillation - raw materials
 forall(p in IDIST) produce(p) <= sum(c in CRUDES) DIST(c,p)*use(c)

! Relations between intermediate products
! Reforming:
 forall(p in IREF) produce(p) <= REF(p)*produce("naphtha")
! Cracking:
 forall(p in ICRACK) produce(p) <= CRACK(p)*produce("residue") 
 produce("crknaphtha") = produce("petcrknaphtha") + 
                         produce("hocrknaphtha") + produce("dslcrknaphtha")
 produce("crkgasoil") = produce("hocrkgasoil") + produce("dslcrkgasoil")
! Desulfurization:
 produce("gasoil") = produce("hogasoil") + produce("dslgasoil")

! Relations final products - intermediate products
 produce("butane") = produce("distbutane") + produce("refbutane") - 
                     produce("petbutane")
 produce("petrol") = sum(p in IPETROL) produce(p)
 produce("diesel") = sum(p in IDIESEL) produce(p)
 produce("heating") = sum(p in IHO) produce(p)

! Properties of petrol
 sum(p in IPETROL) OCT(p)*produce(p) >= 94*produce("petrol")
 sum(p in IPETROL) VAP(p)*produce(p) <= 12.7*produce("petrol")
 sum(p in IPETROL) VOL(p)*produce(p) >= 17*produce("petrol")

! Limit on sulfur in diesel oil
 sum(p in IDIESEL) SULF(p)*produce(p) <= 0.05*produce("diesel")

! Crude availabilities
 forall(c in CRUDES) use(c) <= AVAIL(c)

! Production capacities
 produce("naphtha") <= 30000               ! Reformer
 produce("gasoil") <= 50000                ! Desulfurization
 produce("residue") <= 40000               ! Cracker

! Satisfy demands
 forall(p in FINAL) produce(p) >= DEM(p)

! Solve the problem
 minimize(Cost)

! Solution printing
 writeln("Production costs: ", strfmt(getobjval,10,2))
 forall(c in CRUDES) writeln(c, ": ", getsol(use(c)))
 forall(p in ALLPRODS) writeln(p, ": ", getsol(produce(p)))
 writeln("Petrol properties:")
 writeln(" octane: ", 
   getsol(sum(p in IPETROL) OCT(p)*produce(p))/ getsol(produce("petrol")),
   " vapor presure: ", 
   getsol(sum(p in IPETROL) VAP(p)*produce(p))/ getsol(produce("petrol")),
   " volatility: ", 
   getsol(sum(p in IPETROL) VOL(p)*produce(p))/ getsol(produce("petrol")))
 writeln("Sulfur in diesel oil: ", 
   getsol(sum(p in IDIESEL) SULF(p)*produce(p))/getsol(produce("diesel")) )

end-model 

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

   file a4sugar.mos
   ````````````````
   Production of cane sugar

   Sugar cane harvesting is highly mechanized, however, once
   harvested the sugar content decreases rapidly through 
   fermentation. The sugar content of each wagon depends 
   on maturity of the sugar cane and where it was grown. A 
   production schedule for the current lot must be determined 
   so that it minimizes the total loss of sugar.

   The problem formulation uses binary variables to assign wagons 
   to time slots and 'ceil' in the calculation of an upper bound 
   on the number of time slots needed.

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

model "A-4 Cane sugar production"
 uses "mmxprs", "mmsystem"
 
 declarations
  NW = 11                          ! Number of wagon loads of sugar
  NL = 3                           ! Number of production lines
  WAGONS = 1..NW
  SLOTS = 1..ceil(NW/NL)           ! Time slots for production
  
  LOSS: array(WAGONS) of real      ! Loss in kg/hour
  LIFE: array(WAGONS) of real      ! Remaining time per lot 
  DUR: integer                     ! Duration of the production

  process: array(WAGONS,SLOTS) of mpvar  ! 1 if wagon processed in slot, 
                                         ! 0 otherwise 
 end-declarations
 
 initializations from 'a4sugar.dat'
  LOSS LIFE DUR
 end-initializations

! Objective function  
 TotalLoss:= sum(w in WAGONS, s in SLOTS) s*DUR*LOSS(w)*process(w,s)

! Assignment
 forall(w in WAGONS) sum(s in SLOTS) process(w,s) = 1

! Wagon loads per time slot
 forall(s in SLOTS) sum(w in WAGONS) process(w,s) <= NL
 
! Limit on raw product life
 forall(w in WAGONS) sum(s in SLOTS) s*process(w,s) <= LIFE(w)/DUR

 forall(w in WAGONS, s in SLOTS) process(w,s) is_binary

! Solve the problem
 minimize(TotalLoss)

! Solution printing
 writeln("Total loss: ", getobjval)
 forall(s in SLOTS) do
  write("Slot ", s, ": ")
  forall(w in WAGONS | getsol(process(w,s))>0) 
    write(formattext("wagon %2d (%3g)  ", w, s*DUR*LOSS(w)))
  writeln
 end-do
 
end-model

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

   file a5mine.mos
   ```````````````
   Opencast mining
  
   An opencast uranium mine is being prospected. 6 of 
   the 18 blocks contain uranium. To extract a block, 3
   blocks of the level above it need to be extracted. 
   Blocks have varied extraction costs and each block 
   of uranium has a different market value. The objective
   is to determine which blocks to extract to maximize 
   total benefit.
   
   This model uses binary variables to indicate which 
   blocks will be extracted. There is also a two-dimensional 
   array to enforce the extraction order between layers.
   A relaxed formulation of this constraint is commented out 
   for reference.

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

model "A-5 Opencast mining"
 uses "mmxprs"

 declarations
  BLOCKS = 1..18                       ! Set of blocks
  LEVEL23: set of integer              ! Blocks in levels 2 and 3
  COST: array(BLOCKS) of real          ! Exploitation cost of blocks
  VALUE: array(BLOCKS) of real         ! Value of blocks
  ARC: array(LEVEL23,1..3) of integer  ! Arcs indicating order of extraction

  extract: array(BLOCKS) of mpvar      ! 1 if block b is extracted
 end-declarations

 initializations from 'a5mine.dat'
  COST VALUE ARC
 end-initializations

! Objective: maximize total profit 
 Profit:= sum(b in BLOCKS) (VALUE(b)-COST(b))* extract(b)  

! Extraction order
! forall(b in LEVEL23) 3*extract(b) <= sum(i in 1..3) extract(ARC(b,i))
 forall(b in LEVEL23)
  forall(i in 1..3) extract(b) <= extract(ARC(b,i))

 forall(b in BLOCKS) extract(b) is_binary
  
! Solve the problem
 maximize(Profit)

! Solving LP relaxation only
! maximize(XPRS_LIN, Profit)

! Solution printing
 declarations
  WEIGHT: integer                      ! Weight of blocks 
 end-declarations

 initializations from 'a5mine.dat'
  WEIGHT
 end-initializations

 writeln("Total profit:", getobjval*WEIGHT)
 write("Extract blocks")
 forall(b in BLOCKS | getsol(extract(b))>0) write(" ", b)
 writeln 

end-model

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

   file a5mine_set.mos
   ```````````````````
   Opencast mining
   - Set version -
  
   An opencast uranium mine is being prospected. 6 of 
   the 18 blocks contain uranium. To extract a block, 3
   blocks of the level above it need to be extracted. 
   Blocks have varied extraction costs and each block 
   of uranium has a different market value. The objective
   is to determine which blocks to extract to maximize 
   total benefit.
   
   This model uses binary variables to indicate which 
   blocks will be extracted. The extraction order between 
   layers is represented via an array of sets data structure.
   A relaxed (aggregated) formulation of this constraint is 
   commented out for reference.

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

model "A-5 Opencast mining (2)"
 uses "mmxprs"

 declarations
  BLOCKS = 1..18                         ! Set of blocks
  LEVEL23: set of integer                ! Blocks in levels 2 and 3
  COST: array(BLOCKS) of real            ! Exploitation cost of blocks
  VALUE: array(BLOCKS) of real           ! Value of blocks
  PRED: array(LEVEL23) of set of integer ! Predecessor blocks

  extract: array(BLOCKS) of mpvar        ! 1 if block b is extracted
 end-declarations

 initializations from 'a5mine2.dat'
  COST VALUE PRED
 end-initializations

! Objective: maximize total profit 
 Profit:= sum(b in BLOCKS) (VALUE(b)-COST(b))* extract(b)  

! Extraction order
! forall(b in LEVEL23) getsize(PRED(b))*extract(b) <= sum(c in PRED(b)) extract(c)
 forall(b in LEVEL23) forall(c in PRED(b)) extract(b) <= extract(c)

 forall(b in BLOCKS) extract(b) is_binary
  
! Solve the problem
 maximize(Profit)

! Solution printing
 declarations
  WEIGHT: integer                        ! Weight of blocks 
 end-declarations

 initializations from 'a5mine2.dat'
  WEIGHT
 end-initializations

 writeln("Total profit:", strfmt(getobjval*WEIGHT,8,0))
 write("Extract blocks")
 forall(b in BLOCKS | getsol(extract(b))>0) write(" ", b)
 writeln 

end-model

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

   file a6electr.mos
   `````````````````
   Production of electricity

   Four types of power generators are available to meet daily
   electricity demands and up to 20% above. Each type of 
   generator has a set maximum capacity and minimum power output.
   A generator can only be started or stopped at the beginning 
   of a time period. The objective is to determine which 
   generators should be used in each period so that total daily 
   cost is minimized.   

   Three variable arrays are required to determine when to 'start'
   generators, which ones are set to 'work' in each time period, and
   the energy productionl ('padd') of each type above the minimum 
   output level. 'work' is defined as integer. 'start' is the 
   difference between 'work' this period and 'work' last period and 
   therefore is automatically integer.

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

model "A-6 Electricity production"
 uses "mmxprs", "mmsystem"
 
 declarations
  NT = 7
  TIME = 1..NT                       ! Time periods
  TYPES = 1..4                       ! Power generator types  

  LEN, DEM: array(TIME) of integer   ! Length and demand of time periods 
  PMIN,PMAX: array(TYPES) of integer ! Min. & max output of a generator type
  CSTART: array(TYPES) of integer    ! Start-up cost of a generator
  CMIN: array(TYPES) of integer      ! Hourly cost of gen. at min. output
  CADD: array(TYPES) of real         ! Cost/hour/MW of prod. above min. level
  AVAIL: array(TYPES) of integer     ! Number of generators per type

  start: array(TYPES,TIME) of mpvar  ! No. of gen.s started in a period
  work: array(TYPES,TIME) of mpvar   ! No. of gen.s working during a period
  padd: array(TYPES,TIME) of mpvar   ! Production above min. output level
 end-declarations
 
 initializations from 'a6electr.dat'
  LEN DEM PMIN PMAX CSTART CMIN CADD AVAIL
 end-initializations 
 
! Objective function: total daily cost 
 Cost:= sum(p in TYPES, t in TIME) (CSTART(p)*start(p,t) +
          LEN(t)*(CMIN(p)*work(p,t) + CADD(p)*padd(p,t))) 
                                   
! Number of generators started per period and per type
 forall(p in TYPES, t in TIME) 
  start(p,t) >= work(p,t) - if(t>1, work(p,t-1), work(p,NT))

! Limit on power production above minimum level
 forall(p in TYPES, t in TIME) padd(p,t) <= (PMAX(p)-PMIN(p))*work(p,t)

! Satisfy demands
 forall(t in TIME) sum(p in TYPES) (PMIN(p)*work(p,t) + padd(p,t)) >= DEM(t)

! Security reserve of 20%
 forall(t in TIME) sum(p in TYPES) PMAX(p)*work(p,t) >= 1.20*DEM(t)

! Limit number of available generators; numbers of generators are integer
 forall(p in TYPES, t in TIME) do
  work(p,t) <= AVAIL(p)
  work(p,t) is_integer
 end-do

! Solve the problem  
 minimize(Cost)

! Solution printing
 writeln("Daily cost: ", getobjval)

 write(strfmt("Time period ",-20))
 ct:=0
 forall(t in TIME) do
  write(formattext("%5d-%2d", ct, ct+LEN(t)))
  ct+=LEN(t)
 end-do 

 forall(p in TYPES) do
  write(formattext("\nType %d%-14s", p, " No. working ")); 
  forall(t in TIME) write(strfmt(work(p,t).sol,8))
  write("\n", strfmt("Total output ",20)); 
  forall(t in TIME) write(strfmt(getsol((PMIN(p)*work(p,t) + padd(p,t))),8))
  write("\n", strfmt("of which add.",20)); 
  forall(t in TIME) write(strfmt(padd(p,t).sol,8))
 end-do
 writeln

end-model

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

   file a6electrg.mos
   ``````````````````
   Production of electricity.
   Plotting parametrics in the reserve capacity.

   Four types of power generators are available to meet daily
   electricity demands and up to 20% above. Each type of 
   generator has a set maximum capacity and minimum power output.
   A generator can only be started or stopped at the beginning 
   of a time period. The objective is to determine which 
   generators should be used in each period so that total daily 
   cost is minimized.   

   Similar model formulation as a6electr.mos however defines data
   directly in code and is set up to solve for varying reserve 
   demand (0-20%), redefining the reserve constraints for every loop 
   iteration and reloading the basis saved after the initial LP solve.
   Displays results with a graph.
   
   (c) 2008 Fair Isaac Corporation
       author: S. Heipcke, Oct. 2004, rev. June 2017
*******************************************************!)

model "A-6 Electricity production (with graph drawing)"
 uses "mmxprs", "mmsvg"
 
 declarations
  NT = 7
  TIME = 1..NT                       ! Time periods
  TYPES = 1..4                       ! Power generator types  

  LEN, DEM: array(TIME) of integer   ! Length and demand of time periods 
  PMIN,PMAX: array(TYPES) of integer ! Min. & max output of a generator type
  CSTART: array(TYPES) of integer    ! Start-up cost of a generator
  CMIN: array(TYPES) of integer      ! Hourly cost of gen. at min. output
  CADD: array(TYPES) of real         ! Cost/hour/MW of prod. above min. level
  AVAIL: array(TYPES) of integer     ! Number of generators per type
  bas: basis                         ! LP basis

  start: array(TYPES,TIME) of mpvar  ! No. of gen.s started in a period
  work: array(TYPES,TIME) of mpvar   ! No. of gen.s working during a period
  padd: array(TYPES,TIME) of mpvar   ! Production above min. output level
 end-declarations
 
! Time period data
 LEN:: [    6,     3,     3,     2,     4,     4,     2]
 DEM:: [12000, 32000, 25000, 36000, 25000, 30000, 18000]

! Power plant data
 PMIN::   [ 750, 1000, 1200, 1800]
 PMAX::   [1750, 1500, 2000, 3500]
 CSTART:: [5000, 1600, 2400, 1200]
 CMIN::   [2250, 1800, 3750, 4800]
 CADD::   [ 2.7,  2.2,  1.8,  3.8]
 AVAIL::  [  10,    4,    8,    3]
 
 
! Objective function: total daily cost 
 Cost:= sum(p in TYPES, t in TIME) (CSTART(p)*start(p,t) +
          LEN(t)*(CMIN(p)*work(p,t) + CADD(p)*padd(p,t))) 
                                   
! Number of generators started per period and per type
 forall(p in TYPES, t in TIME) 
  NumStart(p,t):= start(p,t) >= work(p,t) - if(t>1, work(p,t-1), work(p,NT))

! Limit on power production above minimum level
 forall(p in TYPES, t in TIME) 
  Limit(p,t):= padd(p,t) <= (PMAX(p)-PMIN(p))*work(p,t)

! Satisfy demands
 forall(t in TIME) 
  Demand(t):= sum(p in TYPES) (PMIN(p)*work(p,t) + padd(p,t)) >= DEM(t)

! Security reserve (reserve initially at 0%)
 forall(t in TIME) 
  Reserve(t):= sum(p in TYPES) PMAX(p)*work(p,t) >= DEM(t)

! Limit number of available generators; numbers of generators are integer
 forall(p in TYPES, t in TIME) do
  work(p,t) <= AVAIL(p)
  work(p,t) is_integer
 end-do


! Uncomment the following line to see the Optimizer log
! setparam("XPRS_verbose", true)

! Solve as an LP problem and save the basis
 setparam("XPRS_PRESOLVE", 0)
 minimize(XPRS_LPSTOP, Cost)
 savebasis(bas)
 setparam("XPRS_PRESOLVE", 1)

! Define a user graph
 svgaddgroup("Graph", "Reserve %")

! Solve the problem with different values of reserve (from 0% to 20%) 
 forall(r in 0..20) do
  forall(t in TIME)                   ! Redefine the reserve constraints
   Reserve(t):= sum(p in TYPES) PMAX(p)*work(p,t) >= (1+r/100)*DEM(t)

  loadprob(Cost)                      ! Load problem into the Optimizer
  loadbasis(bas)                      ! Load the saved basis
  minimize(Cost)                      ! Solve the modified problem

  writeln(r, "%: ", getobjval)        ! Print solution value
  svgaddpoint("Graph", r, getobjval/1000)  ! Display solution in user graph
 end-do

! Scale the size of the displayed graph
 svgsetgraphscale(10)
 svgsetgraphpointsize(3)

 svgsave("a6electr.svg")
 svgrefresh
 svgwaitclose
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.