NAG Library Manual, Mark 28.5
Interfaces:  FL   CL   CPP   AD 

NAG FL Interface Introduction
Example description
    Program g03eafe

!     G03EAF Example Program Text

!     Mark 28.5 Release. NAG Copyright 2022.

!     .. Use Statements ..
      Use nag_library, Only: g03eaf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Integer                          :: i, ifail, ld, ldx, lj, m, n, uj
      Character (1)                    :: dist, scal, update
      Character (80)                   :: fmt
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: d(:), s(:), x(:,:)
      Integer, Allocatable             :: isx(:)
!     .. Executable Statements ..
      Write (nout,*) 'G03EAF Example Program Results'
      Write (nout,*)

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

!     Read in the problem size
      Read (nin,*) n, m

!     Read in information on the type of distance matrix to use
      Read (nin,*) update, dist, scal

      ldx = n
      ld = n*(n-1)/2
      Allocate (x(ldx,m),isx(m),s(m),d(ld))

!     Read in the data used to construct distance matrix
      Read (nin,*)(x(i,1:m),i=1,n)

!     Read in variable inclusion flags
      Read (nin,*) isx(1:m)

!     Read in scaling
      If (scal=='G' .Or. scal=='g') Then
        Read (nin,*) s(1:m)
      End If

!     Compute the distance matrix
      ifail = 0
      Call g03eaf(update,dist,scal,n,m,x,ldx,isx,s,d,ifail)

!     Display results
      Write (nout,*) ' Distance Matrix'
      Write (nout,*)
      Write (fmt,99999) '(3X,', n - 1, 'I8)'
      Write (nout,fmt)(i,i=1,n-1)
      Write (nout,*)
      Write (fmt,99999) '(1X,I2,2X,', n - 1, '(3X,F5.2))'
      Do i = 2, n
        lj = (i-1)*(i-2)/2 + 1
        uj = i*(i-1)/2
        Write (nout,fmt) i, d(lj:uj)
      End Do

99999 Format (A,I0,A)
    End Program g03eafe