Program g03fcfe

!     G03FCF Example Program Text

!     Mark 25 Release. NAG Copyright 2014.

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

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

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

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

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

!     Use default values for number of iterations and options
      iter = 0
      iopt = 0

!     Perform multi-dimensional scaling
      ifail = 0
      Call g03fcf(typ,n,ndim,d,x,ldx,stress,dfit,iter,iopt,wk,iwk,ifail)

!     Display the results
      Write (nout,99999) 'STRESS = ', stress
      Write (nout,*)
      Flush (nout)
      ifail = 0
      Call x04caf('General',' ',n,ndim,x,ldx,'Co-ordinates',ifail)

99999 Format (10X,A,E13.4)
    End Program g03fcfe