Program f08nbfe ! F08NBF Example Program Text ! Mark 24 Release. NAG Copyright 2012. ! .. Use Statements .. Use nag_library, Only: dgeevx, nag_wp, x02ajf ! .. Implicit None Statement .. Implicit None ! .. Parameters .. Integer, Parameter :: nb = 64, nin = 5, nout = 6 ! .. Local Scalars .. Complex (Kind=nag_wp) :: eig Real (Kind=nag_wp) :: abnrm, eps, tol Integer :: i, ihi, ilo, info, j, lda, ldvl, & ldvr, lwork, n Logical :: pair ! .. Local Arrays .. Real (Kind=nag_wp), Allocatable :: a(:,:), rconde(:), rcondv(:), & scale(:), vl(:,:), vr(:,:), wi(:), & work(:), wr(:) Real (Kind=nag_wp) :: dummy(1) Integer, Allocatable :: iwork(:) ! .. Intrinsic Procedures .. Intrinsic :: cmplx, max, nint ! .. Executable Statements .. Write (nout,*) 'F08NBF Example Program Results' ! Skip heading in data file Read (nin,*) Read (nin,*) n lda = n ldvl = n ldvr = n lwork = (2+nb)*n Allocate (a(lda,n),rconde(n),rcondv(n),scale(n),vl(ldvl,n),vr(ldvr,n), & wi(n),wr(n),iwork(2*n-2)) ! Use routine workspace query to get optimal workspace. lwork = -1 ! The NAG name equivalent of dgeevx is f08nbf Call dgeevx('Balance','Vectors (left)','Vectors (right)', & 'Both reciprocal condition numbers',n,a,lda,wr,wi,vl,ldvl,vr,ldvr,ilo, & ihi,scale,abnrm,rconde,rcondv,dummy,lwork,iwork,info) ! Make sure that there is enough workspace for blocksize nb. lwork = max((nb+2)*n,nint(dummy(1))) Allocate (work(lwork)) ! Read the matrix A from data file Read (nin,*)(a(i,1:n),i=1,n) ! Solve the eigenvalue problem ! The NAG name equivalent of dgeevx is f08nbf Call dgeevx('Balance','Vectors (left)','Vectors (right)', & 'Both reciprocal condition numbers',n,a,lda,wr,wi,vl,ldvl,vr,ldvr,ilo, & ihi,scale,abnrm,rconde,rcondv,work,lwork,iwork,info) If (info==0) Then ! Compute the machine precision eps = x02ajf() tol = eps*abnrm pair = .False. ! Print the eigenvalues and vectors, and associated condition ! number and bounds Write (nout,*) Write (nout,*) 'Eigenvalues' Write (nout,*) Write (nout,*) ' Eigenvalue rcond error' Do j = 1, n ! Print information on jth eigenvalue If (wi(j)==0.0_nag_wp) Then If (rconde(j)>0.0_nag_wp) Then If (tol/rconde(j)<10.0_nag_wp*eps) Then Write (nout,99999) j, wr(j), rconde(j), '-' Else Write (nout,99998) j, wr(j), rconde(j), tol/rconde(j) End If Else Write (nout,99998) j, wr(j), rconde(j), 'Inf' End If Else If (rconde(j)>0.0_nag_wp) Then If (tol/rconde(j)<10.0_nag_wp*eps) Then Write (nout,99997) j, wr(j), wi(j), rconde(j), '-' Else Write (nout,99996) j, wr(j), wi(j), rconde(j), tol/rconde(j) End If Else Write (nout,99997) j, wr(j), wi(j), rconde(j), 'Inf' End If End If End Do Write (nout,*) Write (nout,*) 'Eigenvectors' Write (nout,*) Write (nout,*) ' Eigenvector rcond error' Do j = 1, n ! Print information on jth eigenvector Write (nout,*) If (wi(j)==0.0E0_nag_wp) Then ! Make real eigenvectors have positive first entry If (vr(1,j)<0.0_nag_wp) Then vr(1:n,j) = -vr(1:n,j) End If If (rcondv(j)>0.0_nag_wp) Then If (tol/rcondv(j)<10.0_nag_wp*eps) Then Write (nout,99999) j, vr(1,j), rcondv(j), '-' Else Write (nout,99998) j, vr(1,j), rcondv(j), tol/rcondv(j) End If Else Write (nout,99998) j, vr(1,j), rcondv(j), 'Inf' End If Write (nout,99995) vr(2:n,j) Else If (pair) Then eig = cmplx(vr(1,j-1),-vr(1,j),kind=nag_wp) Else eig = cmplx(vr(1,j),vr(1,j+1),kind=nag_wp) End If If (rcondv(j)>0.0_nag_wp) Then If (tol/rcondv(j)<10.0_nag_wp*eps) Then Write (nout,99997) j, eig, rcondv(j), '-' Else Write (nout,99996) j, eig, rcondv(j), tol/rcondv(j) End If Else Write (nout,99997) j, eig, rcondv(j), 'Inf' End If If (pair) Then Write (nout,99994)(vr(i,j-1),-vr(i,j),i=2,n) Else Write (nout,99994)(vr(i,j),vr(i,j+1),i=2,n) End If pair = .Not. pair End If End Do Write (nout,*) Write (nout,*) 'Errors below 10*machine precision are not displayed' Else Write (nout,*) Write (nout,99993) 'Failure in DGEEVX. INFO = ', info End If 99999 Format (1X,I2,2X,1P,E11.4,14X,0P,F7.4,4X,A) 99998 Format (1X,I2,2X,1P,E11.4,11X,0P,F7.4,1X,1P,E8.1) 99997 Format (1X,I2,1X,'(',1P,E11.4,',',E11.4,')',1X,0P,F7.4,4X,A) 99996 Format (1X,I2,1X,'(',1P,E11.4,',',E11.4,')',1X,0P,F7.4,1X,1P,E8.1) 99995 Format (1X,4X,1P,E11.4) 99994 Format (1X,3X,'(',1P,E11.4,',',E11.4,')') 99993 Format (1X,A,I4) End Program f08nbfe