PROGRAM g03fcfe

!      G03FCF Example Program Text

!      Mark 23 Release. NAG Copyright 2011.

!      .. Use Statements ..
       USE nag_library, ONLY : g01agf, 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 Functions ..
       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)
       WRITE (nout,*)
       WRITE (nout,*) ' Plot of first two dimensions'
       WRITE (nout,*)
       FLUSH (nout)
       ifail = 0
       CALL g01agf(x(1,1),x(1,2),n,iwk,50,18,ifail)

99999  FORMAT (10X,A,E13.4)
    END PROGRAM g03fcfe