Program f08wpfe
! F08WPF Example Program Text
! Mark 28.7 Release. NAG Copyright 2022.
! .. Use Statements ..
Use nag_library, Only: f06bnf, m01daf, m01eaf, m01edf, nag_wp, x02ajf, &
x02amf, zggevx
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nb = 64, nin = 5, nout = 6
Logical, Parameter :: verbose = .False.
! .. Local Scalars ..
Complex (Kind=nag_wp) :: eig, scal
Real (Kind=nag_wp) :: abnorm, abnrm, bbnrm, eps, small, &
tol
Integer :: i, ifail, ihi, ilo, info, j, k, lda, &
ldb, ldvr, lwork, n
! .. Local Arrays ..
Complex (Kind=nag_wp), Allocatable :: a(:,:), alpha(:), b(:,:), beta(:), &
temp(:), vr(:,:), work(:)
Complex (Kind=nag_wp) :: dummy(1,1)
Real (Kind=nag_wp), Allocatable :: lscale(:), rconde(:), rcondv(:), &
rscale(:), rwork(:)
Integer, Allocatable :: irank(:), iwork(:)
Logical, Allocatable :: bwork(:)
! .. Intrinsic Procedures ..
Intrinsic :: abs, max, maxloc, nint, real
! .. Executable Statements ..
Write (nout,*) 'F08WPF Example Program Results'
! Skip heading in data file
Read (nin,*)
Read (nin,*) n
lda = n
ldb = n
ldvr = n
Allocate (a(lda,n),alpha(n),b(ldb,n),beta(n),vr(ldvr,n),lscale(n), &
rconde(n),rcondv(n),rscale(n),rwork(6*n),iwork(n+2),bwork(n),temp(n))
! Use routine workspace query to get optimal workspace.
lwork = -1
! The NAG name equivalent of zggevx is f08wpf
Call zggevx('Balance','No vectors (left)','Vectors (right)', &
'Both reciprocal condition numbers',n,a,lda,b,ldb,alpha,beta,dummy,1, &
vr,ldvr,ilo,ihi,lscale,rscale,abnrm,bbnrm,rconde,rcondv,dummy,lwork, &
rwork,iwork,bwork,info)
! Make sure that there is enough workspace for block size nb.
lwork = max((nb+2*n)*n,nint(real(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 zggevx is f08wpf
Call zggevx('Balance','No vectors (left)','Vectors (right)', &
'Both reciprocal condition numbers',n,a,lda,b,ldb,alpha,beta,dummy,1, &
vr,ldvr,ilo,ihi,lscale,rscale,abnrm,bbnrm,rconde,rcondv,work,lwork, &
rwork,iwork,bwork,info)
If (info>0) Then
Write (nout,*)
Write (nout,99999) 'Failure in ZGGEVX. 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
! Reorder eigenvalues by descending absolute value
rwork(1:n) = abs(alpha(1:n)/beta(1:n))
Allocate (irank(n))
ifail = 0
Call m01daf(rwork,1,n,'Descending',irank,ifail)
Call m01edf(alpha,1,n,irank,ifail)
Call m01edf(beta,1,n,irank,ifail)
Call m01eaf(rconde,1,n,irank,ifail)
! Reorder eigenvectors accordingly
Do j = 1, n
temp(1:n) = vr(j,1:n)
Call m01edf(temp,1,n,irank,ifail)
vr(j,1:n) = temp(1:n)
End Do
Call m01eaf(rcondv,1,n,irank,ifail)
! Print out eigenvalues and vectors and associated condition
! number and bounds
Write (nout,*)
Write (nout,*) 'Eigenvalues'
Write (nout,*)
If (verbose) Then
Write (nout,*) ' Eigenvalue rcond error'
Else
Write (nout,*) ' Eigenvalue'
End If
Do j = 1, n
! Print out information on the j-th eigenvalue
If ((abs(alpha(j)))*small>=abs(beta(j))) Then
If (rconde(j)>0.0_nag_wp) Then
If (tol/rconde(j)<500.0_nag_wp*eps) Then
Write (nout,99995) j, rconde(j), '-'
Else
Write (nout,99994) j, rconde(j), tol/rconde(j)
End If
Else
Write (nout,99995) j, rconde(j), 'Inf'
End If
Else
eig = alpha(j)/beta(j)
If (verbose) Then
If (rconde(j)>0.0_nag_wp) Then
If (tol/rconde(j)<500.0_nag_wp*eps) Then
Write (nout,99998) j, eig, rconde(j), '-'
Else
Write (nout,99997) j, eig, rconde(j), tol/rconde(j)
End If
Else
Write (nout,99998) j, eig, rconde(j), 'Inf'
End If
Else
Write (nout,99998) j, eig
End If
End If
End Do
Write (nout,*)
Write (nout,*) 'Eigenvectors'
Write (nout,*)
If (verbose) Then
Write (nout,*) ' Eigenvector rcond error'
Else
Write (nout,*) ' Eigenvector'
End If
Do j = 1, n
! Print information on j-th eigenvector
Write (nout,*)
! Re-normalize eigenvector, largest absolute element real (=1)
rwork(1:n) = abs(vr(1:n,j))
k = maxloc(rwork(1:n),1)
scal = (1.0_nag_wp,0.0_nag_wp)/vr(k,j)
vr(1:n,j) = vr(1:n,j)*scal
If (verbose) Then
If (rcondv(j)>0.0_nag_wp) Then
If (tol/rcondv(j)<500.0_nag_wp*eps) Then
Write (nout,99998) j, vr(1,j), rcondv(j), '-'
Else
Write (nout,99997) j, vr(1,j), rcondv(j), tol/rcondv(j)
End If
Else
Write (nout,99998) j, vr(1,j), rcondv(j), 'Inf'
End If
Else
Write (nout,99998) j, vr(1,j)
End If
Write (nout,99996) vr(2:n,j)
End Do
If (verbose) Then
Write (nout,*)
Write (nout,*) &
'Errors below 500*machine precision are not displayed'
End If
End If
99999 Format (1X,A,I4)
99998 Format (1X,I2,1X,'(',1P,E11.4,',',E11.4,')',1X,0P,F7.4,4X,A)
99997 Format (1X,I2,1X,'(',1P,E11.4,',',E11.4,')',1X,0P,F7.4,1X,1P,E8.1)
99996 Format (1X,3X,'(',1P,E11.4,',',E11.4,')')
99995 Format (1X,I2,1X,' Infinite or undetermined',1X,0P,F7.4,4X,A)
99994 Format (1X,I2,1X,' Infinite or undetermined',1X,0P,F7.4,1X,1P,E8.1)
End Program f08wpfe