Initializing help system before first use

F. Air transport


Description:

Problem name and type, features Difficulty
F‑1 Flight connections at a hub: Assignment problem *
F‑2 Composing flight crews: Bipartite matching ****
2 problems, data preprocessing, incremental definition of data array, encoding of arcs, logical or (cumulative version) and and, procedure for printing solution, forall-do, max, finalize
F‑3 Scheduling flight landings: Scheduling problem with time windows ***
generalization of model to arbitrary time windows; calculation of specific BigM, forall-do
F‑4 Airline hub location: Hub location problem ***
quadruple indices; improved (re)formulation (first model not usable with student version), union of index (range) sets
F‑5 Planning a flight tour: Symmetric traveling salesman problem *****
loop over problem solving, TSP subtour elimination algorithm; procedure for generating additional constraints, recursive subroutine calls, working with sets, forall-do, repeat-until, getsize, not


File(s): f1connect.mos (Mar. 2002), f2crew.mos (Mar. 2002), f3landing.mos (Mar. 2002), f4hub.mos (Mar. 2002), f4hub2.mos (Jul. 2002), f4hub3.mos (Dec. 2008), f5tour.mos (Mar. 2002), f5tour2.mos (Jun. 2002)
Data file(s): f1connect.dat, f2crew.dat, f3landing.dat, f4hub.dat, f5tour.dat, f5tour23.dat, f5tour7.dat

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

   file f1connect.mos
   ``````````````````
   Planning flight connections at a hub
   
   (c) 2008 Fair Isaac Corporation
       author: S. Heipcke, Mar. 2002
*******************************************************!)

model "F-1 Flight connections"
 uses "mmxprs"

 declarations
  PLANES = 1..6                         ! Set of airplanes
  
  PASS: array(PLANES,PLANES) of integer ! Passengers with flight connections
  
  cont: array(PLANES,PLANES) of mpvar   ! 1 if flight i continues to j
 end-declarations

 initializations from 'f1connect.dat'
  PASS
 end-initializations

! Objective: number of passengers on connecting flights
 Transfer:= sum(i,j in PLANES) PASS(i,j)*cont(i,j)

! One incoming and one outgoing flight per plane
 forall(i in PLANES) sum(j in PLANES) cont(i,j) = 1
 forall(j in PLANES) sum(i in PLANES) cont(i,j) = 1

 forall(i,j in PLANES) cont(i,j) is_binary

! Solve the problem: maximize the number of passengers staying on board
 maximize(Transfer)
 
! Solution printing
 writeln("Passengers staying on board: ", getobjval)
 forall(i in PLANES)
 writeln(i, " -> ", getsol(sum(j in PLANES) j*cont(i,j)), " (",
         getsol(sum(j in PLANES) PASS(i,j)*cont(i,j)), ")")
 
end-model

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

   file f2crew.mos
   ```````````````
   Composing military flight crews
   
   (c) 2008 Fair Isaac Corporation
       author: S. Heipcke, Mar. 2002
*******************************************************!)

model "F-2 Flight crews"
 uses "mmxprs"

 forward procedure print_sol

 declarations
  PILOTS = 1..8                      ! Set of pilots
  ARCS: range                        ! Set of arcs representing crews
  RL, RT: set of string              ! Sets of languages and plane types

  LANG: array(RL,PILOTS) of integer  ! Language skills of pilots
  PTYPE: array(RT,PILOTS) of integer ! Flying skills of pilots
  CREW: array(ARCS,1..2) of integer  ! Possible crews
 end-declarations

 initializations from 'f2crew.dat'
  LANG PTYPE
 end-initializations

! Calculate the possible crews
 ct:=1
 forall(p,q in PILOTS| p<q and 
                      (or(l in RL) (LANG(l,p)>=10 and LANG(l,q)>=10)) and
                      (or(t in RT) (PTYPE(t,p)>=10 and PTYPE(t,q)>=10)) ) do
  CREW(ct,1):=p
  CREW(ct,2):=q
  ct+=1
 end-do

 finalize(ARCS)
 
 declarations
  fly: array(ARCS) of mpvar           ! 1 if crew is flying, 0 otherwise
 end-declarations 
 
! First objective: number of pilots flying
 NFlying:= sum(a in ARCS) fly(a)

! Every pilot is member of at most a single crew
 forall(r in PILOTS) sum(a in ARCS | CREW(a,1)=r or CREW(a,2)=r) fly(a) <= 1

 forall(a in ARCS) fly(a) is_binary
 
! Solve the problem
 maximize(NFlying)
 
! Solution printing
 writeln("Number of crews: ", getobjval)
 print_sol

! **** Extend the problem ****
 declarations
  SCORE: array(ARCS) of integer       ! Maximum scores of crews  
 end-declarations 

 forall(a in ARCS)
  SCORE(a):= max(t in RT | PTYPE(t,CREW(a,1))>=10 and PTYPE(t,CREW(a,2))>=10) 
               (PTYPE(t,CREW(a,1)) + PTYPE(t,CREW(a,2)))

! Second objective: sum of scores
 TotalScore:= sum(a in ARCS) SCORE(a)*fly(a)

! Solve the problem
 maximize(TotalScore)

 writeln("Maximum total score: ", getobjval)
 print_sol
 
!-----------------------------------------------------------------

! Solution printing
 procedure print_sol
  forall(a in ARCS)
   if(getsol(fly(a))>0) then
    writeln(CREW(a,1),  " - ", CREW(a,2))
   end-if
 end-procedure  
  
end-model

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

   file f3landing.mos
   ``````````````````
   Schedule plane landings
   
   (c) 2008 Fair Isaac Corporation
       author: S. Heipcke, Mar. 2002
*******************************************************!)

model "F-3 Landing schedule"
 uses "mmxprs"

 declarations
  PLANES = 1..10                        ! Set of airplanes
  
  START, STOP: array(PLANES) of integer ! Start, end of arrival time windows
  TARGET: array(PLANES) of integer      ! Planned arrival times
  CEARLY, CLATE: array(PLANES) of integer ! Cost of earliness/lateness
  DIST: array(PLANES,PLANES) of integer ! Minimum interval between planes
  M: array(PLANES,PLANES) of integer    ! Sufficiently large positive values
  
  prec: array(PLANES,PLANES) of mpvar   ! 1 if plane i precedes j
  land: array(PLANES) of mpvar          ! Arrival time
  early,late: array(PLANES) of mpvar    ! Earliness/lateness
 end-declarations

 initializations from 'f3landing.dat'
  START STOP TARGET CEARLY CLATE DIST
 end-initializations

 forall(p,q in PLANES) M(p,q):= STOP(p) + DIST(p,q) - START(q)

! Objective: total penalty for deviations from planned arrival times
 Cost:= sum(p in PLANES) (CEARLY(p)*early(p) + CLATE(p)*late(p))

! Keep required intervals between plan arrivals
 forall(p,q in PLANES | p>q)
  land(p) + DIST(p,q) <= land(q) + M(p,q)*prec(q,p)
 forall(p,q in PLANES | p<q)
  land(p) + DIST(p,q) <= land(q) + M(p,q)*(1-prec(p,q))

! Relations between earliness, lateness, and effective arrival time
 forall(p in PLANES) do
  early(p) >= TARGET(p) - land(p)
  late(p) >= land(p) - TARGET(p)
  land(p) = TARGET(p) - early(p) + late(p)
 end-do

 forall(p in PLANES) do
  START(p) <= land(p); land(p) <= STOP(p)
  early(p) <= TARGET(p)-START(p)
  late(p) <= STOP(p)-TARGET(p)
 end-do
 
 forall(p,q in PLANES | p<q) prec(p,q) is_binary 

! Solve the problem
 minimize(Cost)
 
! Solution printing
 writeln("Total deviation cost: ", getobjval)
 writeln("Plane Arrival Target Deviation")
 forall(p in PLANES) 
  writeln(strfmt(p,3), strfmt(getsol(land(p)),8), strfmt(TARGET(p),8), 
          strfmt(getsol(land(p))-TARGET(p),8))

end-model

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

   file f4hub.mos
   ``````````````
   Choosing hubs for transatlantic freight
   
   (c) 2008 Fair Isaac Corporation
       author: S. Heipcke, Mar. 2002
*******************************************************!)

model "F-4 Hubs"
 uses "mmxprs"

 declarations
  CITIES = 1..6                          ! Cities
  NHUBS = 2                              ! Number of hubs
  
  COST: array(CITIES,CITIES,CITIES,CITIES) of real ! (i,j,k,l) Transport cost
                                         ! from i to j via hubs k and l
  QUANT: array(CITIES,CITIES) of integer ! Quantity to transport
  DIST: array(CITIES,CITIES) of integer  ! Distance between cities
  FACTOR: real                           ! Reduction of costs between hubs
  
  flow: array(CITIES,CITIES,CITIES,CITIES) of mpvar ! flow(i,j,k,l)=1 if 
                                         ! freight from i to j goes via k & l 
  hub: array(CITIES) of mpvar            ! 1 if city is a hub, 0 otherwise
 end-declarations

 initializations from 'f4hub.dat'
  QUANT DIST FACTOR
 end-initializations

! Calculate costs
 forall(i,j,k,l in CITIES) 
  COST(i,j,k,l):= DIST(i,k)+FACTOR*DIST(k,l)+DIST(l,j)

! Objective: total transport cost
 Cost:= sum(i,j,k,l in CITIES) QUANT(i,j)*COST(i,j,k,l)*flow(i,j,k,l)

! Number of hubs
 sum(i in CITIES) hub(i) = NHUBS
 
! One hub-to-hub connection per freight transport 
 forall(i,j in CITIES) sum(k,l in CITIES) flow(i,j,k,l) = 1
 
! Relation between flows and hubs
 forall(i,j,k,l in CITIES) do
  flow(i,j,k,l) <= hub(k)
  flow(i,j,k,l) <= hub(l)
 end-do 

 forall(i in CITIES) hub(i) is_binary
 forall(i,j,k,l in CITIES) flow(i,j,k,l) is_binary

! Solve the problem
 minimize(Cost)
 
! Solution printing
 declarations
  NAMES: array(CITIES) of string         ! Names of cities
 end-declarations 

 initializations from 'f4hub.dat'
  NAMES
 end-initializations

 writeln("Total transport cost: ", strfmt(getobjval,10,2))
 write("Hubs:")
 forall(i in CITIES) write( if(getsol(hub(i))>0," " + NAMES(i), ""))
 writeln
 
end-model

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

   file f4hub2.mos
   ```````````````
   Choosing hubs for transatlantic freight
   (second, improved formulation)
   
   (c) 2008 Fair Isaac Corporation
       author: S. Heipcke, Jul. 2002
*******************************************************!)

model "F-4 Hubs (2)"
 uses "mmxprs"

 forward function calc_cost(i,j,k,l:integer):real

 declarations
  US = 1..3; EU = 4..6
  CITIES = US + EU                       ! Cities
  NHUBS = 2                              ! Number of hubs
  
  QUANT: array(CITIES,CITIES) of integer ! Quantity to transport
  DIST: array(CITIES,CITIES) of integer  ! Distance between cities
  FACTOR: real                           ! Reduction of costs between hubs
  
  flow: dynamic array(CITIES,CITIES,CITIES,CITIES) of mpvar
                                         ! flow(i,j,k,l)=1 if freight
                                         ! from i to j goes via k and l 
  hub: array(CITIES) of mpvar            ! 1 if city is a hub, 0 otherwise
 end-declarations

 initializations from 'f4hub.dat'
  QUANT DIST FACTOR
 end-initializations

 forall(i,j in CITIES | i<j) QUANT(i,j):=QUANT(i,j)+QUANT(j,i)

 forall(i,j,k in US | i<j) create(flow(i,j,k,k))
 forall(i,j,k in EU | i<j) create(flow(i,j,k,k))
 forall(i,k in US, j,l in EU) create(flow(i,j,k,l))

! Objective: total transport cost
 Cost:= sum(i,j,k,l in CITIES | exists(flow(i,j,k,l))) 
                   QUANT(i,j)*calc_cost(i,j,k,l)*flow(i,j,k,l)

! Number of hubs
 sum(i in CITIES) hub(i) = NHUBS
 
! One hub-to-hub connection per freight transport 
 forall(i,j in CITIES | i<j) sum(k,l in CITIES) flow(i,j,k,l) = 1
 forall(i,j in US | i<j) sum(k in US) flow(i,j,k,k) = 1
 forall(i,j in EU | i<j) sum(k in EU) flow(i,j,k,k) = 1
 
! Relation between flows and hubs
 forall(i,j,k,l in CITIES | exists(flow(i,j,k,l))) do
  flow(i,j,k,l) <= hub(k)
  flow(i,j,k,l) <= hub(l)
 end-do 

 forall(i in CITIES) hub(i) is_binary
 forall(i,j,k,l in CITIES | exists(flow(i,j,k,l))) flow(i,j,k,l) is_binary

! Solve the problem
 minimize(Cost)
 
! Solution printing
 declarations
  NAMES: array(CITIES) of string         ! Names of cities
 end-declarations 

 initializations from 'f4hub.dat'
  NAMES
 end-initializations

 writeln("Total transport cost: ", strfmt(getobjval,10,2))
 write("Hubs:")
 forall(i in CITIES) write( if(getsol(hub(i))>0," " + NAMES(i), ""))
 writeln

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

! Transport cost from i to j via hubs k and l
 function calc_cost(i,j,k,l:integer):real
  returned:=DIST(i,k)+FACTOR*DIST(k,l)+DIST(l,j)
 end-function
   
end-model

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

   file f4hub3.mos
   ```````````````
   Choosing hubs for transatlantic freight
   (number of hubs specified as a model parameter)
   
   (c) 2008 Fair Isaac Corporation
       author: S. Heipcke, Dec. 2008
*******************************************************!)

model "F-4 Hubs (2)"
 uses "mmxprs"

 parameters
  NHUBS = 2                              ! Number of hubs
 end-parameters 

 forward function calc_cost(i,j,k,l:integer):real

 declarations
  US = 1..3; EU = 4..6
  CITIES = US + EU                       ! Cities
  
  QUANT: array(CITIES,CITIES) of integer ! Quantity to transport
  DIST: array(CITIES,CITIES) of integer  ! Distance between cities
  FACTOR: real                           ! Reduction of costs between hubs
  
  flow: dynamic array(CITIES,CITIES,CITIES,CITIES) of mpvar
                                         ! flow(i,j,k,l)=1 if freight
                                         ! from i to j goes via k and l 
  hub: array(CITIES) of mpvar            ! 1 if city is a hub, 0 otherwise
 end-declarations

 initializations from 'f4hub.dat'
  QUANT DIST FACTOR
 end-initializations

 forall(i,j in CITIES | i<j) QUANT(i,j):=QUANT(i,j)+QUANT(j,i)

 forall(i,j,k,l in US | i<j) create(flow(i,j,k,l))
 forall(i,j,k,l in EU | i<j) create(flow(i,j,k,l))
 forall(i,k in US, j,l in EU) create(flow(i,j,k,l))

! Objective: total transport cost
 Cost:= sum(i,j,k,l in CITIES | exists(flow(i,j,k,l))) 
                   QUANT(i,j)*calc_cost(i,j,k,l)*flow(i,j,k,l)

! Number of hubs
 sum(i in CITIES) hub(i) = NHUBS
 
! One hub-to-hub connection per freight transport 
 forall(i,j in CITIES | i<j) sum(k,l in CITIES) flow(i,j,k,l) = 1
 forall(i,j in US | i<j) sum(k,l in US) flow(i,j,k,l) = 1
 forall(i,j in EU | i<j) sum(k,l in EU) flow(i,j,k,l) = 1
 
! Relation between flows and hubs
 forall(i,j,k,l in CITIES | exists(flow(i,j,k,l))) do
  flow(i,j,k,l) <= hub(k)
  flow(i,j,k,l) <= hub(l)
 end-do 

 forall(i in CITIES) hub(i) is_binary
 forall(i,j,k,l in CITIES | exists(flow(i,j,k,l))) flow(i,j,k,l) is_binary

! Solve the problem
 minimize(Cost)
 
! Solution printing
 declarations
  NAMES: array(CITIES) of string         ! Names of cities
 end-declarations 

 initializations from 'f4hub.dat'
  NAMES
 end-initializations

 writeln("Total transport cost: ", strfmt(getobjval,10,2))
 write("Hubs:")
 forall(i in CITIES) write( if(getsol(hub(i))>0," " + NAMES(i), ""))
 writeln

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

! Transport cost from i to j via hubs k and l
 function calc_cost(i,j,k,l:integer):real
  returned:=DIST(i,k)+FACTOR*DIST(k,l)+DIST(l,j)
 end-function
   
end-model

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

   file f5tour.mos
   ```````````````
   Planning a flight tour
   
   (c) 2008 Fair Isaac Corporation
       author: S. Heipcke, Mar. 2002, rev. Mar. 2014
*******************************************************!)

model "F-5 Tour planning"
 uses "mmxprs"

 forward procedure break_subtour
 forward procedure print_sol

 declarations
  NCITIES = 7
  CITIES = 1..NCITIES                    ! Cities
  
  DIST: array(CITIES,CITIES) of integer  ! Distance between cities
  NEXTC: array(CITIES) of integer        ! Next city after i in the solution
  
  fly: array(CITIES,CITIES) of mpvar     ! 1 if flight from i to j 
 end-declarations

 initializations from 'f5tour.dat'
  DIST
 end-initializations

 forall(i,j in CITIES | i<j) DIST(j,i):=DIST(i,j)

! Objective: total distance
 TotalDist:= sum(i,j in CITIES | i<>j) DIST(i,j)*fly(i,j)

! Visit every city once
 forall(i in CITIES) sum(j in CITIES | i<>j) fly(i,j) = 1
 forall(j in CITIES) sum(i in CITIES | i<>j) fly(i,j) = 1

 forall(i,j in CITIES | i<>j) fly(i,j) is_binary

! Solve the problem
 minimize(TotalDist)

! Eliminate subtours
 break_subtour

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

 procedure break_subtour
  declarations
   TOUR,SMALLEST,ALLCITIES: set of integer
  end-declarations

  forall(i in CITIES) 
   NEXTC(i):= integer(round(getsol(sum(j in CITIES) j*fly(i,j) )))

! Print the current solution  
  print_sol
  
! Get (sub)tour containing city 1
  TOUR:={}
  first:=1
  repeat
   TOUR+={first}
   first:=NEXTC(first)
  until first=1
  size:=getsize(TOUR)
 
! Find smallest subtour
  if size < NCITIES then
   SMALLEST:=TOUR
   if size>2 then
    ALLCITIES:=TOUR 
    forall(i in CITIES) do
     if(i not in ALLCITIES) then
      TOUR:={}
      first:=i
      repeat
       TOUR+={first}
       first:=NEXTC(first)
      until first=i
      ALLCITIES+=TOUR
      if getsize(TOUR)<size then
       SMALLEST:=TOUR
       size:=getsize(SMALLEST)
      end-if
      if size=2 then
       break
      end-if 
     end-if 
    end-do        
   end-if
    
! Add a subtour breaking constraint
  sum(i in SMALLEST) fly(i,NEXTC(i)) <= getsize(SMALLEST) - 1

! Optional: Also exclude the inverse subtour
  if SMALLEST.size>2 then
   sum(i in SMALLEST) fly(NEXTC(i),i) <= getsize(SMALLEST) - 1
  end-if

! Optional: Add a stronger subtour elimination cut
   sum(i in SMALLEST,j in CITIES-SMALLEST) fly(i,j) >= 1
 
! Re-solve the problem
   minimize(TotalDist)

   break_subtour
  end-if 
 end-procedure
 
!-----------------------------------------------------------------

! Print the current solution
 procedure print_sol
  declarations
   ALLCITIES: set of integer
  end-declarations
   
  writeln("Total distance: ", getobjval)
  ALLCITIES:={}
  forall(i in CITIES) do
   if(i not in ALLCITIES) then
    write(i)
    first:=i
    repeat
     ALLCITIES+={first}
     write(" - ", NEXTC(first))
     first:=NEXTC(first)
    until first=i
    writeln 
   end-if
  end-do        
 end-procedure

end-model

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

   file f5tour2.mos
   ````````````````
   Problem 9.6: Planning a flight tour
   (second formulation for other data format)
   
   (c) 2008 Fair Isaac Corporation
       author: S. Heipcke, Jun. 2002, rev. Mar. 2014
*******************************************************!)

model "F-5 Tour planning (2)"
 uses "mmxprs", "mmsystem"

 parameters
  DATAFILE="f5tour23.dat"
 end-parameters 

 forward procedure break_subtour
 forward procedure print_sol

 declarations
  starttime: real
  CITIES: set of string                  ! Set of cities
 end-declarations

 starttime:=gettime

 initializations from DATAFILE
  CITIES
 end-initializations

 finalize(CITIES)

 declarations
  NCITIES=getsize(CITIES)
  
  DIST: array(CITIES,CITIES) of integer  ! Distance between cities
  NEXTC: array(CITIES) of string         ! Next city after i in the solution

  fly: array(CITIES,CITIES) of mpvar     ! 1 if flight from i to j 
 end-declarations

 initializations from DATAFILE
  DIST
 end-initializations

! Objective: total distance
 TotalDist:= sum(i,j in CITIES | i<>j) DIST(i,j)*fly(i,j)

! Visit every city once
 forall(i in CITIES) sum(j in CITIES | i<>j) fly(i,j) = 1
 forall(j in CITIES) sum(i in CITIES | i<>j) fly(i,j) = 1

 forall(i,j in CITIES | i<>j) fly(i,j) is_binary

! Solve the problem
 minimize(TotalDist)

! Eliminate subtours
 break_subtour

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

 procedure break_subtour
  declarations
   TOUR,SMALLEST,ALLCITIES: set of string
   TOL=10E-10
  end-declarations

  forall(i in CITIES) 
   forall(j in CITIES)
    if(getsol(fly(i,j))>=1-TOL) then 
     NEXTC(i):=j
     break
    end-if
     
! Print the current solution  
  print_sol
  
! Get (sub)tour containing city 1
  TOUR:={}
  first:="Bordeaux"
  repeat
   TOUR+={first}
   first:=NEXTC(first)
  until first="Bordeaux"
  size:=getsize(TOUR)
 
! Find smallest subtour
  if size < NCITIES then
   SMALLEST:=TOUR
   if size>2 then
    ALLCITIES:=TOUR 
    forall(i in CITIES) do
     if(i not in ALLCITIES) then
      TOUR:={}
      first:=i
      repeat
       TOUR+={first}
       first:=NEXTC(first)
      until first=i
      ALLCITIES+=TOUR
      if getsize(TOUR)<size then
       SMALLEST:=TOUR
       size:=getsize(SMALLEST)
      end-if
      if size=2 then
       break
      end-if 
     end-if 
    end-do        
   end-if
    
! Add a subtour breaking constraint
   sum(i in SMALLEST) fly(i,NEXTC(i)) <= getsize(SMALLEST) - 1

! Optional: Also exclude the inverse subtour
  if SMALLEST.size>2 then
   sum(i in SMALLEST) fly(NEXTC(i),i) <= getsize(SMALLEST) - 1
  end-if

! Optional: Add a stronger subtour elimination cut
   sum(i in SMALLEST,j in CITIES-SMALLEST) fly(i,j) >= 1
  
! Re-solve the problem
   minimize(TotalDist)

   break_subtour
  end-if 
 end-procedure
 
!-----------------------------------------------------------------

! Print the current solution
 procedure print_sol
  declarations
   ALLCITIES: set of string
  end-declarations
   
  writeln("(", gettime-starttime, "s) Total distance: ", getobjval)
  ALLCITIES:={}
  forall(i in CITIES) do
   if(i not in ALLCITIES) then
    write(i)
    first:=i
    repeat
     ALLCITIES+={first}
     write(" - ", NEXTC(first))
     first:=NEXTC(first)
    until first=i
    writeln 
   end-if
  end-do        
 end-procedure

end-model

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