Program g03fafe

!     G03FAF Example Program Text

!     Mark 25 Release. NAG Copyright 2014.

!     .. Use Statements ..
      Use nag_library, Only: g03faf, nag_wp, x04caf
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Integer                          :: ifail, ld, ldx, liwk, lwk, n, ndim
      Character (1)                    :: roots
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: d(:), eval(:), wk(:), x(:,:)
      Integer, Allocatable             :: iwk(:)
!     .. Executable Statements ..
      Write (nout,*) 'G03FAF Example Program Results'
      Write (nout,*)

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

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

      ld = n*(n-1)/2
      ldx = n
      lwk = n*(n+17)/2 - 1
      liwk = 5*n
      Allocate (d(ld),x(ldx,ndim),eval(n),wk(lwk),iwk(liwk))

!     Read in the lower triangular part of the distance matrix
      Read (nin,*) d(1:ld)

!     Perform principal co-ordinate analysis
      ifail = 0
      Call g03faf(roots,n,d,ndim,x,ldx,eval,wk,iwk,ifail)

!     Display results
      Write (nout,*) ' Scaled Eigenvalues'
      Write (nout,*)
      If (roots=='L' .Or. roots=='l') Then
        Write (nout,99999) eval(1:ndim)
      Else
        Write (nout,99999) eval(1:n)
      End If
      Write (nout,*)
      Flush (nout)
      ifail = 0
      Call x04caf('General',' ',n,ndim,x,ldx,'Co-ordinates',ifail)

99999 Format (8F10.4)
    End Program g03fafe