Program g03ecfe ! G03ECF Example Program Text ! Mark 24 Release. NAG Copyright 2012. ! .. Use Statements .. Use nag_library, Only: g03eaf, g03ecf, nag_wp ! .. Implicit None Statement .. Implicit None ! .. Parameters .. Integer, Parameter :: nin = 5, nout = 6, rnlen = 3 ! .. Local Scalars .. Integer :: i, ifail, 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 :: ilc(:), iord(:), isx(:), iuc(:), & iwk(:) Character (rnlen), Allocatable :: row_name(:) ! .. Executable Statements .. Write (nout,*) 'G03ECF 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),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 results Write (nout,*) ' Distance Clusters Joined' Write (nout,*) Write (nout,99999)(cd(i),row_name(ilc(i)),row_name(iuc(i)),i=1,n1) 99999 Format (F10.3,5X,2A) End Program g03ecfe