Initializing help system before first use

G. Telecommunication problems


Description:

Problem name and type, features Difficulty Related examples
G‑1 Network reliability: Maximum flow with unitary capacities *** maxflow_graph.mos, j1water.mos
encoding of arcs, range, exists, create, algorithm for printing paths, forall-do, while-do, round, list handling
G‑2 Dimensioning of a mobile phone network **
if-then, exit
G‑3 Routing telephone calls: Multi-commodity network flow problem *** multicomflow_graph.mos
encoding of paths, finalize, getsize
G‑4 Construction of a cabled network: Minimum weight spanning tree problem *** spanningtree_graph.mos
formulation of constraints to exclude subcycles
G‑5 Scheduling of telecommunications via satellite: Preemptive open shop scheduling ***** openshop_graph.mos
data preprocessing, algorithm for preemptive scheduling that involves looping over optimization, ``Gantt chart'' printing
G‑6 Location of GSM transmitters: Covering problem * covering_graph.mos, d5cutsh.mos, j2bigbro.mos
modeling an equivalence; sparse data format


File(s): g1rely.mos (Mar. 2002), g2dimens.mos (Apr. 2002), g3routing.mos (Apr. 2002), g4cable.mos (Apr. 2002), g5satell.mos (Apr. 2002), g6transmit.mos (Apr. 2002)
Data file(s): g1rely.dat, g2dimens.dat, g3routing.dat, g4cable.dat, g5satell.dat, g6transmit.dat

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

   file g1rely.mos
   ```````````````
   Reliability of a telecommunications network

   A military telecommunications network has eleven sites
   connected by bidirectional lines for data transmission.
   Due to reliability reasons, node 10 and 11 must remain
   able to communicate even if any three other sites are
   destroyed. Is this possible given the current network
   configuration?

   This problem can be modeled as a maximum flow problem
   where the graph with N nodes is encoded as an adjacency
   matrix. To create a more compact model, the variables
   'flow' are only defined for existing arcs. Since there is
   a bidirectional connection between each node, only one
   direction is provided in the data and we define the
   opposite direction within the code. We use the function
   'round' to transform the result of 'getsol' from 'real'
   to 'integer'.

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

model "G-1 Network reliability"
 uses "mmxprs"

 declarations
  NODES: range                        ! Set of nodes
  SOURCE = 10; SINK = 11              ! Source and sink nodes 

  ARC: dynamic array(NODES,NODES) of integer ! 1 if arc defined, 0 otherwise
  
  flow: dynamic array(NODES,NODES) of mpvar  ! 1 if flow on arc, 0 otherwise
 end-declarations

 initializations from 'g1rely.dat'
  ARC
 end-initializations

 forall(n,m in NODES | exists(ARC(n,m)) and n<m ) ARC(m,n):= ARC(n,m)
 forall(n,m in NODES | exists(ARC(n,m)) )  create(flow(n,m))

! Objective: number of disjunctive paths
 Paths:= sum(n in NODES) flow(SOURCE,n)

! Flow conservation and capacities
 forall(n in NODES | n<>SOURCE and n<>SINK) do
  sum(m in NODES) flow(m,n) = sum(m in NODES) flow(n,m)
  sum(m in NODES) flow(n,m) <= 1
 end-do 

! No return to SOURCE node
 sum(n in NODES) flow(n,SOURCE) = 0

 forall(n,m in NODES | exists(ARC(n,m)) )  flow(n,m) is_binary

! Solve the problem
 maximize(Paths)
 
! Solution printing
 writeln("Total number of paths: ", getobjval)

 forall(n in NODES | n<>SOURCE and n<>SINK and getsol(flow(SOURCE,n))>0) do
  write(SOURCE, " - ",n)
  nnext:=n
  while (nnext<>SINK) do
   nnext:=round(getsol(sum(m in NODES) m*flow(nnext,m)))
   write(" - ", nnext)
  end-do
  writeln
 end-do

! Alternative solution display storing paths in a list structure
 declarations
  SolPath: array(range) of list of integer
 end-declarations
  
 forall(n in NODES | n<>SOURCE and n<>SINK and getsol(flow(SOURCE,n))>0, 
        i as counter) do
  SolPath(i):= [SOURCE, n]
  while (SolPath(i).last<>SINK)
   SolPath(i) += [round(getsol(sum(m in NODES) m*flow(SolPath(i).last,m)))]
 end-do
 writeln("Paths: ", SolPath)

end-model

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

   file g2dimens.mos
   `````````````````
   Diminsioning of a mobile phone network
   
   Consider a network of 10 cells and a 5-node ring of hubs 
   (simple hubs + one MTSO=Mobile Telephone Switching Office
   that controls the network) with defined capacity. 
   The more links between a cell and the ring increases
   the reliability of the network. The traffic in this type of 
   system is equivalent to bidirectional circuits. The capacity 
   is the number of simultaneous calls during peak periods. The
   required number of connections, forecasted traffic, and the
   cost per connection is known. Which connections of cells to
   the ring minimize the connection costs while still meeting 
   the traffic demand within the capacity limit?
   
   First, ensure that the ring capacity is sufficiently large to 
   meet all the traffic requirements with an 'if-then' condition.
   If not, the function 'exit' is used to stop the execution. 
   A simple MIP formulation follows.

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

model "G-2 Mobile network dimensioning"
 uses "mmxprs"

 declarations
  HUBS = 1..4
  MTSO = 5                                ! Node number of MTSO
  NODES = HUBS+{MTSO}                     ! Set of nodes (simple hubs + MTSO)
  CELLS = 1..10                           ! Cells to connect 

  CAP: integer                            ! Capacity of ring segments
  COST: array(CELLS,NODES) of integer     ! Connection cost
  TRAF: array(CELLS) of integer           ! Traffic from every cell
  CNCT: array(CELLS) of integer           ! Connections of a cell to the ring 
  
  ifconnect: array(CELLS,NODES) of mpvar  ! 1 if cell connected to node, 
                                          ! 0 otherwise
 end-declarations

 initializations from 'g2dimens.dat'
  CAP COST TRAF CNCT
 end-initializations

! Check ring capacity
 if not (sum(c in CELLS) TRAF(c)*(1-1/CNCT(c)) <= 2*CAP) then
  writeln("Ring capacity not sufficient")
  exit(0)
 end-if 

! Objective: total cost
 TotCost:= sum(c in CELLS, n in NODES) COST(c,n)*ifconnect(c,n)

! Number of connections per cell
 forall(c in CELLS) sum(n in NODES) ifconnect(c,n) = CNCT(c) 

! Ring capacity
 sum(c in CELLS, n in HUBS) (TRAF(c)/CNCT(c))*ifconnect(c,n) <= 2*CAP

 forall(c in CELLS, n in NODES) ifconnect(c,n) is_binary

! Solve the problem
 minimize(TotCost)
 
! Solution printing
 writeln("Total cost: ", getobjval, " (total traffic in the ring: ",
   getsol(sum(c in CELLS, n in HUBS) (TRAF(c)/CNCT(c))*ifconnect(c,n)), ")")

 forall(c in CELLS) do
  write(c, " ->")
  forall(n in NODES | getsol(ifconnect(c,n))>0) write(" ", n)
  writeln
 end-do 

end-model

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

   file g3routing.mos
   ``````````````````
   Routing telephone calls in a private network
   
   A private telephone network connects 5 French cities.
   The circuit capacity between cities is known. At any point
   in time, the network expects certain circuit demands. Is it
   feasible to satisfy all these demands? How much can be 
   transmitted, if not all? Which is the assigned routing for 
   the circuits?
   
   Each path between cities is represented by a list of arcs 
   (specified as an array) between two directly connected cities. 
   The problem is defined as a MIP, but the LP solution 
   already provides integer values. The solution display reports 
   unmet demand and also calculates the unused arc capacities.
      
   (c) 2008 Fair Isaac Corporation
       author: S. Heipcke, Apr. 2002
*******************************************************!)

model "G-3 Routing telephone calls"
 uses "mmxprs"

 declarations
  CALLS: set of string                  ! Set of demands
  ARCS: set of string                   ! Set of arcs 
  PATHS: range                          ! Set of paths (routes) for demands

  CAP: array(ARCS) of integer           ! Capacity of arcs
  DEM: array(CALLS) of integer          ! Demands between pairs of cities
  CINDEX: array(PATHS) of string        ! Call (demand) index per path index 
 end-declarations

 initializations from 'g3routing.dat'
  CAP DEM CINDEX
 end-initializations

 NARC:=getsize(ARCS)

 declarations
  ROUTE: array(PATHS,1..NARC) of string ! List of arcs composing the routes
  flow: array(PATHS) of mpvar           ! Flow on paths
 end-declarations

 initializations from 'g3routing.dat'
  ROUTE
 end-initializations

! Objective: total flow on the arcs
 TotFlow:= sum(p in PATHS) flow(p)

! Flow within demand limits
 forall(d in CALLS) sum(p in PATHS | CINDEX(p) = d) flow(p) <= DEM(d) 

! Arc capacities
 forall(a in ARCS) 
  sum(p in PATHS, b in 1..NARC | ROUTE(p,b)=a) flow(p) <= CAP(a)

 forall(p in PATHS) flow(p) is_integer

! Uncomment to display the solver log
! setparam("XPRS_VERBOSE", true)

! Solve the problem
 maximize(TotFlow)
 
! Solution printing
 writeln("Total flow: ", getobjval)

 forall(d in CALLS) do
  writeln(d, " (demand: ", DEM(d), ", routed calls: ",
    getsol(sum(p in PATHS | CINDEX(p) = d) flow(p)), ")")
  forall(p in PATHS | CINDEX(p) = d and getsol(flow(p))>0) do 
   write("  ", getsol(flow(p)), ":")
   forall(b in 1..NARC) write(" ", ROUTE(p,b))
   writeln
  end-do 
 end-do 

 writeln("Unused capacity:")
 forall(a in ARCS) do 
  U:=CAP(a) - getsol(sum(p in PATHS, b in 1..NARC | ROUTE(p,b)=a) flow(p))
  write(if(U>0,"  " + a + ": " + U + "\n", ""))
 end-do

end-model

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

   file g4cable.mos
   ````````````````
   Connecting terminals through cables

   A university wants to connect 6 terminals located in
   different campus buildings. These terminals will be
   connected via underground cables. The connection cost
   is proportional to the distance between the terminals.
   Which connections should be installed to minimize total
   cost?

   Simple constraints defining the number of total connections
   and that each terminal must be connected to another
   terminal could result in a sub cycle leading to an infeasible
   solution. Each node is assigned a level value that is used in
   the formulation of additional constraints to exclude the
   creation of sub cycles.

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

model "G-4 Cabled network"
 uses "mmxprs"

 declarations
  NTERM = 6
  TERMINALS = 1..NTERM                  ! Set of terminals to connect

  DIST: array(TERMINALS,TERMINALS) of integer     ! Distance between terminals

  ifconnect: array(TERMINALS,TERMINALS) of mpvar  ! 1 if direct connection
                                        ! between terminals, 0 otherwise
  level: array(TERMINALS) of mpvar      ! level value of nodes
 end-declarations

 initializations from 'g4cable.dat'
  DIST
 end-initializations

! Objective: length of cable used
 Length:= sum(s,t in TERMINALS | s<>t) DIST(s,t)*ifconnect(s,t)

! Number of connections
 sum(s,t in TERMINALS | s<>t) ifconnect(s,t) = NTERM - 1 

! Avoid subcycle
 forall(s,t in TERMINALS | s<>t) 
  level(t) >= level(s) + 1 - NTERM + NTERM*ifconnect(s,t)

! Direct all connections towards the root (node 1)
 forall(s in 2..NTERM) sum(t in TERMINALS | s<>t) ifconnect(s,t) = 1

 forall(s,t in TERMINALS | s<>t) ifconnect(s,t) is_binary

! Solve the problem
 minimize(Length)
 
! Solution printing
 writeln("Cable length: ", getobjval)

 write("Connections:")
 forall(s,t in TERMINALS | s<>t and getsol(ifconnect(s,t))>0)
  write(" ", s, "-", t) 
 writeln
  
end-model

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

   file g5satell.mos
   `````````````````
   Scheduling of telecommunications via satellite
   
   A digital telecommunications system via satellite contains
   a satellite and a set of stations on earth. The satellite 
   divides its time between the stations. Consider 4 transmitting
   stations in the U.S. and 4 receiving stations in Europe. 
   The quantity of data transmitted between stations is known.
   A specific permutation of connections of transmitters and 
   receivers that allows routing part of the traffic is called 
   a 'mode'. The portion of a traffic demand transmitted during 
   a mode is a 'packet' of data. The duration of a mode is the 
   length of its longest packet. Determine the schedule of
   satellite modes with minimal total duration.
   
   This program implements the algorithm of Gonzalez and 
   Sahni. The inter-station traffic must be translated into
   a quasi bistochastic matrix via data preprocessing. The 
   problem definition is then incremental so that after each 
   solution of the MIP, the matrix is updated. Since the entire 
   problem is redefined in every iteration of the 'while' loop,
   each constraint is named so that they may be replaced. Note
   that once the 'flow' variables are defined they cannot be 
   removed. The final solution is printed as a Gantt chart
   showing the traffic leaving each of the 4 U.S. stations.
   
   (c) 2008 Fair Isaac Corporation
       author: S. Heipcke, Apr. 2002
*******************************************************!)

model "G-5 Satellite scheduling"
 uses "mmxprs"

 declarations
  TRANSM = 1..4                         ! Set of transmitters
  RECV = 1..4                           ! Set of receivers

  TRAF: array(TRANSM,RECV) of integer   ! Traffic betw. terrestrial stations
  TQBS: array(TRANSM,RECV) of integer   ! Quasi bistochastic traffic matrix
  row: array(TRANSM) of integer         ! Row sums
  col: array(RECV) of integer           ! Column sums
  LB: integer                           ! Maximum of row and column sums
 end-declarations

 initializations from 'g5satell.dat'
  TRAF
 end-initializations

! Row and column sums
 forall(t in TRANSM) row(t):= sum(r in RECV) TRAF(t,r)
 forall(r in RECV) col(r):= sum(t in TRANSM) TRAF(t,r)
 LB:=maxlist(max(r in RECV) col(r), max(t in TRANSM) row(t))

! Calculate TQBS 
 forall(t in TRANSM,r in RECV) do
  q:= minlist(LB-row(t),LB-col(r))
  TQBS(t,r):= TRAF(t,r)+q
  row(t)+=q
  col(r)+=q
 end-do

 declarations
  MODES: range
  
  flow: array(TRANSM,RECV) of mpvar         ! 1 if transmission from t to r,
                                            ! 0 otherwise
  pmin: mpvar                               ! Minimum exchange
  onerec, minexchg: array(TRANSM) of linctr ! Constraints on transmitters 
                                            ! and min exchange
  onetrans: array(RECV) of linctr           ! Constraints on receivers

  solflowt: array(TRANSM,MODES) of integer  ! Solutions of every iteration
  solflowr: array(RECV,MODES) of integer    ! Solutions of every iteration   
  solpmin: array(MODES) of integer          ! Objective value per iteration 
 end-declarations

 forall(t in TRANSM,r in RECV) flow(t,r) is_binary

 ct:= 0
 while(sum(t in TRANSM,r in RECV) TQBS(t,r) > 0) do
  ct+=1
  
 ! One receiver per transmitter
  forall(t in TRANSM) onerec(t):= sum(r in RECV | TQBS(t,r)>0) flow(t,r) =1
 ! One transmitter per receiver
  forall(r in RECV) onetrans(r):= sum(t in TRANSM | TQBS(t,r)>0) flow(t,r) =1

 ! Minimum exchange
  forall(t in TRANSM) 
   minexchg(t):= sum(r in RECV | TQBS(t,r)>0) TQBS(t,r)*flow(t,r) >= pmin

 ! Solve the problem: maximize the minimum exchange
  maximize(pmin)

 ! Solution printing
  writeln("Round ", ct, " objective: ", getobjval)

 ! Save the solution
  solpmin(ct):= round(getobjval)
  forall(t in TRANSM,r in RECV | TQBS(t,r)>0 and getsol(flow(t,r))>0) do
   solflowt(t,ct):= t
   solflowr(t,ct):= r
  end-do 

 ! Update TQBS
  forall(t in TRANSM)
   TQBS(solflowt(t,ct),solflowr(t,ct)) -= solpmin(ct)

 end-do
 
! Solution printing
 writeln("\nTotal duration: ", sum(m in MODES) solpmin(m))
 
 write("      ")
 forall(i in 0..ceil(LB/5)) write(strfmt(i*5,5))
 writeln
 forall(t in TRANSM) do
  write("From ", t, " to: ")
  forall(m in MODES)
   forall(i in 1..solpmin(m)) do
    write(if(TRAF(solflowt(t,m),solflowr(t,m))>0, string(solflowr(t,m)),"-"))
    TRAF(solflowt(t,m),solflowr(t,m))-=1
   end-do
  writeln 
 end-do
 
end-model

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

   file g6transmit.mos
   ```````````````````
   Placing mobile phone transmitters

   A mobile phone operator plans to equip a currently uncovered
   region. There are 7 possible locations for the transmitters.
   Each site has a defined number of communities it can serve.
   Given the construction cost and reach of each site, where
   should the transmitters be built so that the largest
   population is covered with the given budget restrictions?

   The formulation as a covering problem is straightforward. 
   We store data for 'COVER' in sparse format, that is, only 
   the entries with value 1 are given. Since this array is 
   declared as a dense array, all other entries are 
   automatically populated with value 0.

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

model "G-6 Transmitter placement"
 uses "mmxprs"

 declarations
  COMMS = 1..15                         ! Set of communities
  PLACES = 1..7                         ! Set of possible transm. locations

  COST: array(PLACES) of real           ! Cost of constructing transmitters
  COVER: array(PLACES,COMMS) of integer ! Coverage by transmitter locations
  POP: array(COMMS) of integer          ! Number of inhabitants (in 1000)
  BUDGET: integer                       ! Budget limit
   
  build: array(PLACES) of mpvar         ! 1 if transmitter built, 0 otherwise
  covered: array(COMMS) of mpvar        ! 1 if community covered, 0 otherwise 
 end-declarations

 initializations from 'g6transmit.dat'
  COST COVER POP BUDGET
 end-initializations

! Objective: total population covered
 Coverage:= sum(c in COMMS) POP(c)*covered(c)

! Towns covered
 forall(c in COMMS) sum(p in PLACES) COVER(p,c)*build(p) >= covered(c) 

! Budget limit
 sum(p in PLACES) COST(p)*build(p) <= BUDGET

 forall(p in PLACES) build(p) is_binary
 forall(c in COMMS) covered(c) is_binary

! Solve the problem
 maximize(Coverage)
 
! Solution printing
 writeln("Total coverage: ", getobjval, " (of ", sum(c in COMMS) POP(c), 
   ") total cost: ", getsol(sum(p in PLACES) COST(p)*build(p)))
 write("Build transmitters:")
 forall(p in PLACES | getsol(build(p))>0) write(" ", p)
 write("\nCommunities covered:")
 forall(c in COMMS | getsol(covered(c))>0) write(" ", c)
 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.