Program f08wbfe ! F08WBF Example Program Text ! Mark 24 Release. NAG Copyright 2012. ! .. Use Statements .. Use nag_library, Only: dggevx, f06bnf, nag_wp, x02ajf, x02amf ! .. 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) :: abnorm, abnrm, bbnrm, eps, erbnd, & rcnd, small, tol Integer :: i, ihi, ilo, info, j, lda, ldb, & ldvr, lwork, n Logical :: pair ! .. Local Arrays .. Real (Kind=nag_wp), Allocatable :: a(:,:), alphai(:), alphar(:), & b(:,:), beta(:), lscale(:), & rconde(:), rcondv(:), rscale(:), & vr(:,:), work(:) Real (Kind=nag_wp) :: dummy(1,1) Integer, Allocatable :: iwork(:) Logical, Allocatable :: bwork(:) ! .. Intrinsic Procedures .. Intrinsic :: abs, cmplx, max, nint, real ! .. Executable Statements .. Write (nout,*) 'F08WBF Example Program Results' ! Skip heading in data file Read (nin,*) Read (nin,*) n lda = n ldb = n ldvr = n Allocate (a(lda,n),alphai(n),alphar(n),b(ldb,n),beta(n),lscale(n), & rconde(n),rcondv(n),rscale(n),vr(ldvr,n),iwork(n+6),bwork(n)) ! Use routine workspace query to get optimal workspace. lwork = -1 ! The NAG name equivalent of dggevx is f08wbf Call dggevx('Balance','No vectors (left)','Vectors (right)', & 'Both reciprocal condition numbers',n,a,lda,b,ldb,alphar,alphai,beta, & dummy,1,vr,ldvr,ilo,ihi,lscale,rscale,abnrm,bbnrm,rconde,rcondv,dummy, & lwork,iwork,bwork,info) ! Make sure that there is enough workspace for blocksize nb. lwork = max((nb+2*n)*n,nint(dummy(1,1))) Allocate (work(lwork)) ! Read in the matrices A and B Read (nin,*)(a(i,1:n),i=1,n) Read (nin,*)(b(i,1:n),i=1,n) ! Solve the generalized eigenvalue problem ! The NAG name equivalent of dggevx is f08wbf Call dggevx('Balance','No vectors (left)','Vectors (right)', & 'Both reciprocal condition numbers',n,a,lda,b,ldb,alphar,alphai,beta, & dummy,1,vr,ldvr,ilo,ihi,lscale,rscale,abnrm,bbnrm,rconde,rcondv,work, & lwork,iwork,bwork,info) If (info>0) Then Write (nout,*) Write (nout,99999) 'Failure in DGGEVX. INFO =', info Else ! Compute the machine precision, the safe range parameter ! small and sqrt(abnrm**2+bbnrm**2) eps = x02ajf() small = x02amf() abnorm = f06bnf(abnrm,bbnrm) tol = eps*abnorm ! Print out eigenvalues and vectors and associated condition ! number and bounds pair = .False. Do j = 1, n ! Print out information on the jth eigenvalue Write (nout,*) If ((abs(alphar(j))+abs(alphai(j)))*small>=abs(beta(j))) Then Write (nout,99998) 'Eigenvalue(', j, ')', & ' is numerically infinite or undetermined', 'ALPHAR(', j, & ') = ', alphar(j), ', ALPHAI(', j, ') = ', alphai(j), ', BETA(', & j, ') = ', beta(j) Else If (alphai(j)==0.0E0_nag_wp) Then Write (nout,99997) 'Eigenvalue(', j, ') = ', alphar(j)/beta(j) Else eig = cmplx(alphar(j),alphai(j),kind=nag_wp)/ & cmplx(beta(j),kind=nag_wp) Write (nout,99996) 'Eigenvalue(', j, ') = ', eig End If End If rcnd = rconde(j) Write (nout,*) Write (nout,99995) 'Reciprocal condition number = ', rcnd If (rcnd>0.0E0_nag_wp) Then erbnd = tol/rcnd Write (nout,99995) 'Error bound = ', erbnd Else Write (nout,*) 'Error bound is infinite' End If ! Print out information on the jth eigenvector ! Make first real part component be positive If (.Not. pair .And. real(vr(1,j),kind=nag_wp)<0.0_nag_wp) Then vr(1:n,j) = -vr(1:n,j) End If Write (nout,*) Write (nout,99994) 'Eigenvector(', j, ')' If (alphai(j)==0.0E0_nag_wp) Then Write (nout,99993)(vr(i,j),i=1,n) Else If (pair) Then Write (nout,99992)(vr(i,j-1),-vr(i,j),i=1,n) Else Write (nout,99992)(vr(i,j),vr(i,j+1),i=1,n) End If pair = .Not. pair End If rcnd = rcondv(j) Write (nout,*) Write (nout,99995) 'Reciprocal condition number = ', rcnd If (rcnd>0.0E0_nag_wp) Then erbnd = tol/rcnd Write (nout,99995) 'Error bound = ', erbnd Else Write (nout,*) 'Error bound is infinite' End If End Do End If 99999 Format (1X,A,I4) 99998 Format (1X,A,I2,2A/1X,2(A,I2,A,1P,E11.4),A,I2,A,1P,E11.4) 99997 Format (1X,A,I2,A,1P,E11.4) 99996 Format (1X,A,I2,A,'(',1P,E11.4,',',1P,E11.4,')') 99995 Format (1X,A,1P,E8.1) 99994 Format (1X,A,I2,A) 99993 Format (1X,1P,E11.4) 99992 Format (1X,'(',1P,E11.4,',',1P,E11.4,')') End Program f08wbfe