Initializing help system before first use

A. Mining and process industries


Description:

Problem name and type, features Difficulty
A‑1 Production of alloys: Blending problem *
formulation of blending constraints; data with numerical indices, solution printout, if-then, getsol
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
A‑3 Refinery : Blending problem **
formulation of blending constraints; sparse data with string indices, dynamic initialization, dynamic arrays, finalize, create, union of sets
A‑4 Cane sugar production : Minimum cost flow (in a bipartite graph) *
ceil, is_binary
A‑5 Opencast mining: Minimum cost flow **
encoding of arcs, solving LP-relaxation only
A‑6 Production of electricity: Dispatch problem **
inline if, is_integer


File(s): a1alloy.mos (Feb. 2002), a2food.mos (Feb. 2002), a3refine.mos (Feb. 2002), a4sugar.mos (Feb. 2002), a5mine.mos (Feb. 2002), a6electr.mos (Mar. 2002)
Data file(s): a1alloy.dat, a2food.dat, a3refine.dat, a4sugar.dat, a5mine.dat, a6electr.dat

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

   file a1alloy.mos
   ````````````````
   Production of alloys   

   (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

   (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
   
   (c) 2008 Fair Isaac Corporation
       author: S. Heipcke, Feb. 2002
*******************************************************!)

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

 finalize(FINAL); finalize(CRUDES); finalize(IPETROL); finalize(IDIESEL) 
 finalize(IDIST); finalize(IREF); finalize(ICRACK)
 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
   
   (c) 2008 Fair Isaac Corporation
       author: S. Heipcke, Feb. 2002
*******************************************************!)

model "A-4 Cane sugar production"
 uses "mmxprs"
 
 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) 
   if(getsol(process(w,s))>0) then
    write("wagon ", strfmt(w,2), strfmt(" (" + s*DUR*LOSS(w) + ")  ", 8))
   end-if 
  writeln
 end-do
 
end-model

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

   file a5mine.mos
   ```````````````
   Opencast mining
   
   (c) 2008 Fair Isaac Corporation
       author: S. Heipcke, Feb. 2002
*******************************************************!)

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)

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

 initializations from 'a5mine.dat'
  WEIGHT
 end-initializations

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

end-model

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

   file a6electr.mos
   `````````````````
   Production of electricity
   
   (c) 2008 Fair Isaac Corporation
       author: S. Heipcke, Mar. 2002
*******************************************************!)

model "A-6 Electricity production"
 uses "mmxprs"
 
 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(strfmt(ct,5), "-", strfmt(ct+LEN(t),2), "")
  ct+=LEN(t)
 end-do 

 forall(p in TYPES) do
  write("\nType ", p, strfmt(" No. working ",-14)); 
  forall(t in TIME) write(strfmt(getsol(work(p,t)),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(getsol(padd(p,t)),8))
 end-do
 writeln

end-model