PROGRAM g03eafe

!      G03EAF Example Program Text

!      Mark 23 Release. NAG Copyright 2011.

!      .. 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