Example description
    Program h03bbfe

!     H03BBF Example Program Text
!     Mark 27.0 Release. NAG Copyright 2019.

!     .. Use Statements ..
      Use nag_library, Only: g05kff, h03bbf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: lseed = 4, nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: bound, cost, targc
      Integer                          :: genid, i, i2, ib, ifail, j, l,       &
                                          lstate, nb, nc, subid, tmode
!     .. Local Arrays ..
      Real (Kind=nag_wp)               :: alg_stats(6)
      Real (Kind=nag_wp), Allocatable  :: dm(:,:)
      Integer, Allocatable             :: path(:), state(:)
      Integer                          :: seed(lseed)
      Character (20), Allocatable      :: cities(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: len_trim, max, min, repeat, trim
!     .. Executable Statements ..

      Write (nout,*) 'H03BBF Example Program Results'
      Write (nout,*)

!     Skip heading in data file
      Read (nin,*)

!     Number of cities
      Read (nin,*) nc

!     Allocate distance matrix and path
      Allocate (path(nc),dm(nc,nc))
!     Read distance matrix 10 columns at a time
      nb = (nc+8)/10
      Do ib = 1, nb
        Read (nin,*)
        Read (nin,*)
        i2 = min(10*ib,nc-1)
        Do i = 1, i2
          Read (nin,*)(dm(i,j),j=max(i+1,10*ib-8),i2+1)
        End Do
      End Do

      Allocate (cities(nc))
      Do i = 1, nc
        Read (nin,*) cities(i)
      End Do

!     Calculate a lower bound internally and try to find lowest cost path.
      bound = -1.0_nag_wp
      targc = -1.0_nag_wp

!     Initialize the random number state array.
!     Use the query mechanism to find the required lstate.
      genid = 2
      subid = 53
      seed(:) = (/304950,889934,209094,23423990/)
      lstate = 0
      Allocate (state(lstate))
      ifail = 0
      Call g05kff(genid,subid,seed,lseed,state,lstate,ifail)
      Deallocate (state)
      Allocate (state(lstate))
      ifail = 0
      Call g05kff(genid,subid,seed,lseed,state,lstate,ifail)

!     Find low cost return path through all cities
      ifail = 0
      Call h03bbf(nc,dm,bound,targc,path,cost,tmode,alg_stats,state,ifail)

      Write (nout,99999) 'Initial search end cost', alg_stats(3)
      Write (nout,99999) 'Search best cost       ', alg_stats(4)
      Write (nout,99999) 'Initial temperature    ', alg_stats(5)
      Write (nout,99999) 'Lower bound            ', alg_stats(6)
      Write (nout,99998) 'Termination mode       ', tmode
      Write (nout,*)
      Write (nout,99999) 'Final cost             ', cost

      Write (nout,*)
      Write (nout,*) 'Final Path:'
      Write (nout,99997) trim(cities(path(1))), trim(cities(path(2)))
      l = len_trim(cities(path(1)))
      Write (nout,99997)(repeat(' ',l),trim(cities(path(i+1))),i=2,nc-1)
      Write (nout,99997) repeat(' ',l), trim(cities(path(1)))
99999 Format (1X,A,':',F12.2)
99998 Format (1X,A,':',I12)
99997 Format (1X,A,' --> ',A)
    End Program h03bbfe