PROGRAM g03ejfe ! G03EJF Example Program Text ! Mark 23 Release. NAG Copyright 2011. ! .. Use Statements .. USE nag_library, ONLY : g03eaf, g03ecf, g03ejf, nag_wp ! .. Implicit None Statement .. IMPLICIT NONE ! .. Parameters .. INTEGER, PARAMETER :: nin = 5, nout = 6, rnlen = 3 ! .. Local Scalars .. REAL (KIND=nag_wp) :: dlevel INTEGER :: i, ifail, k, ld, ldx, liwk, m, & method, n, n1 CHARACTER (1) :: dist, scal, update ! .. Local Arrays .. REAL (KIND=nag_wp), ALLOCATABLE :: cd(:), d(:), dord(:), s(:), x(:,:) INTEGER, ALLOCATABLE :: ic(:), ilc(:), iord(:), isx(:), & iuc(:), iwk(:) CHARACTER (rnlen), ALLOCATABLE :: row_name(:) ! .. Executable Statements .. WRITE (nout,*) 'G03EJF 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 n1 = n - 1 liwk = 2*n ALLOCATE (x(ldx,m),isx(m),s(m),d(ld),ilc(n1),iuc(n1),cd(n1),iord(n), & dord(n),iwk(liwk),ic(n),row_name(n)) ! 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) ! Read in information on the clustering method to use READ (nin,*) method ! Read in first RNLEN characters of row names. Used to make example ! output easier to read READ (nin,*) row_name(1:n) ! Perform clustering ifail = 0 CALL g03ecf(method,n,d,ilc,iuc,cd,iord,dord,iwk,ifail) ! Display full clustering information WRITE (nout,*) ' Distance Clusters Joined' WRITE (nout,*) DO i = 1, n - 1 WRITE (nout,99999) cd(i), row_name(ilc(i)), row_name(iuc(i)) END DO WRITE (nout,*) ! Read in number of clusters required (K) and ! distance (DLEVEL). If K > 0 then DLEVEL is ! ignored (i.e. attempt to find K clusters, ! irrespective of distance), else all clusters at ! level DLEVEL are used READ (nin,*) k, dlevel ! Compute cluster indicator ifail = 0 CALL g03ejf(n,cd,iord,dord,k,dlevel,ic,ifail) ! Display the indicators WRITE (nout,99998) ' Allocation to ', k, ' clusters' WRITE (nout,99996) ' Clusters found at distance ', dlevel WRITE (nout,*) WRITE (nout,*) ' Object Cluster' WRITE (nout,*) WRITE (nout,99997) (row_name(i),ic(i),i=1,n) 99999 FORMAT (1X,F10.3,5X,2A) 99998 FORMAT (1X,A,I0,A) 99997 FORMAT (6X,A,5X,I2) 99996 FORMAT (1X,A,F0.3) END PROGRAM g03ejfe