Program f08yxfe
! F08YXF Example Program Text
! Mark 25 Release. NAG Copyright 2014.
! .. Use Statements ..
Use nag_library, Only: f06tff, f06thf, nag_wp, x04dbf, zgeqrf, zggbak, &
zggbal, zgghrd, zhgeqz, ztgevc, zungqr, zunmqr
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Complex (Kind=nag_wp), Parameter :: cone = (1.0E0_nag_wp,0.0E0_nag_wp)
Complex (Kind=nag_wp), Parameter :: czero = (0.0E0_nag_wp,0.0E0_nag_wp)
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Complex (Kind=nag_wp) :: e
Integer :: i, icols, ifail, ihi, ilo, info, &
irows, jwork, lda, ldb, ldvl, ldvr, &
lwork, m, n
Logical :: ileft, iright
Character (1) :: compq, compz, howmny, job, side
! .. Local Arrays ..
Complex (Kind=nag_wp), Allocatable :: a(:,:), alpha(:), b(:,:), beta(:), &
tau(:), vl(:,:), vr(:,:), work(:)
Real (Kind=nag_wp), Allocatable :: lscale(:), rscale(:), rwork(:)
Logical, Allocatable :: select(:)
Character (1) :: clabs(1), rlabs(1)
! .. Intrinsic Procedures ..
Intrinsic :: aimag, nint, real
! .. Executable Statements ..
Write (nout,*) 'F08YXF Example Program Results'
Flush (nout)
! ileft is TRUE if left eigenvectors are required
! iright is TRUE if right eigenvectors are required
ileft = .True.
iright = .True.
! Skip heading in data file
Read (nin,*)
Read (nin,*) n
lda = n
ldb = n
ldvl = n
ldvr = n
lwork = 6*n
Allocate (a(lda,n),alpha(n),b(ldb,n),beta(n),tau(n),vl(ldvl,ldvl), &
vr(ldvr,ldvr),work(lwork),lscale(n),rscale(n),rwork(6*n),select(n))
! READ matrix A from data file
Read (nin,*)(a(i,1:n),i=1,n)
! READ matrix B from data file
Read (nin,*)(b(i,1:n),i=1,n)
! Balance matrix pair (A,B)
job = 'B'
! The NAG name equivalent of zggbal is f08wvf
Call zggbal(job,n,a,lda,b,ldb,ilo,ihi,lscale,rscale,rwork,info)
! Matrix A after balancing
! ifail: behaviour on error exit
! =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
ifail = 0
Call x04dbf('General',' ',n,n,a,lda,'Bracketed','F7.4', &
'Matrix A after balancing','Integer',rlabs,'Integer',clabs,80,0,ifail)
Write (nout,*)
Flush (nout)
! Matrix B after balancing
ifail = 0
Call x04dbf('General',' ',n,n,b,ldb,'Bracketed','F7.4', &
'Matrix B after balancing','Integer',rlabs,'Integer',clabs,80,0,ifail)
Write (nout,*)
Flush (nout)
! Reduce B to triangular form using QR
irows = ihi + 1 - ilo
icols = n + 1 - ilo
! The NAG name equivalent of zgeqrf is f08asf
Call zgeqrf(irows,icols,b(ilo,ilo),ldb,tau,work,lwork,info)
! Apply the orthogonal transformation to A
! The NAG name equivalent of zunmqr is f08auf
Call zunmqr('L','C',irows,icols,irows,b(ilo,ilo),ldb,tau,a(ilo,ilo),lda, &
work,lwork,info)
! Initialize VL (for left eigenvectors)
If (ileft) Then
Call f06thf('General',n,n,czero,cone,vl,ldvl)
Call f06tff('Lower',irows-1,irows-1,b(ilo+1,ilo),ldb,vl(ilo+1,ilo), &
ldvl)
! The NAG name equivalent of zungqr is f08atf
Call zungqr(irows,irows,irows,vl(ilo,ilo),ldvl,tau,work,lwork,info)
End If
! Initialize VR for right eigenvectors
If (iright) Call f06thf('General',n,n,czero,cone,vr,ldvr)
! Compute the generalized Hessenberg form of (A,B)
compq = 'V'
compz = 'V'
! The NAG name equivalent of zgghrd is f08wsf
Call zgghrd(compq,compz,n,ilo,ihi,a,lda,b,ldb,vl,ldvl,vr,ldvr,info)
! Matrix A in generalized Hessenberg form
ifail = 0
Call x04dbf('General',' ',n,n,a,lda,'Bracketed','F7.3', &
'Matrix A in Hessenberg form','Integer',rlabs,'Integer',clabs,80,0, &
ifail)
Write (nout,*)
Flush (nout)
! Matrix B in generalized Hessenberg form
ifail = 0
Call x04dbf('General',' ',n,n,b,ldb,'Bracketed','F7.3', &
'Matrix B in Hessenberg form','Integer',rlabs,'Integer',clabs,80,0, &
ifail)
! Routine ZHGEQZ
! Workspace query: jwork = -1
jwork = -1
job = 'S'
! The NAG name equivalent of zhgeqz is f08xsf
Call zhgeqz(job,compq,compz,n,ilo,ihi,a,lda,b,ldb,alpha,beta,vl,ldvl,vr, &
ldvr,work,jwork,rwork,info)
Write (nout,*)
Write (nout,99999) nint(real(work(1)))
Write (nout,99998) lwork
Write (nout,*)
Flush (nout)
! Compute the generalized Schur form
! if the workspace lwork is adequate
If (nint(real(work(1)))<=lwork) Then
! The NAG name equivalent of zhgeqz is f08xsf
Call zhgeqz(job,compq,compz,n,ilo,ihi,a,lda,b,ldb,alpha,beta,vl,ldvl, &
vr,ldvr,work,lwork,rwork,info)
! Print the generalized eigenvalues
! Note: the actual values of beta are real and non-negative
Write (nout,99997)
Do i = 1, n
If (real(beta(i))/=0.0E0_nag_wp) Then
e = alpha(i)/beta(i)
Write (nout,99995) i, '(', real(e), ',', aimag(e), ')'
Else
Write (nout,99996) i
End If
End Do
Write (nout,*)
Flush (nout)
! Compute left and right generalized eigenvectors
! of the balanced matrix
howmny = 'B'
If (ileft .And. iright) Then
side = 'B'
Else If (ileft) Then
side = 'L'
Else If (iright) Then
side = 'R'
End If
! The NAG name equivalent of ztgevc is f08yxf
Call ztgevc(side,howmny,select,n,a,lda,b,ldb,vl,ldvl,vr,ldvr,n,m,work, &
rwork,info)
! Compute right eigenvectors of the original matrix
If (iright) Then
job = 'B'
side = 'R'
! The NAG name equivalent of zggbak is f08wwf
Call zggbak(job,side,n,ilo,ihi,lscale,rscale,n,vr,ldvr,info)
! Normalize the right eigenvectors
Do i = 1, n
vr(1:n,i) = vr(1:n,i)/vr(1,i)
End Do
! Print the right eigenvectors
ifail = 0
Call x04dbf('General',' ',n,n,vr,ldvr,'Bracketed','F7.4', &
'Right eigenvectors','Integer',rlabs,'Integer',clabs,80,0,ifail)
Write (nout,*)
Flush (nout)
End If
! Compute left eigenvectors of the original matrix
If (iright) Then
job = 'B'
side = 'L'
! The NAG name equivalent of zggbak is f08wwf
Call zggbak(job,side,n,ilo,ihi,lscale,rscale,n,vl,ldvl,info)
! Normalize the left eigenvectors
Do i = 1, n
vl(1:n,i) = vl(1:n,i)/vl(1,i)
End Do
! Print the left eigenvectors
ifail = 0
Call x04dbf('General',' ',n,n,vl,ldvl,'Bracketed','F7.4', &
'Left eigenvectors','Integer',rlabs,'Integer',clabs,80,0,ifail)
End If
Else
Write (nout,99994)
End If
99999 Format (1X,'Minimal required LWORK = ',I6)
99998 Format (1X,'Actual value of LWORK = ',I6)
99997 Format (1X,'Generalized eigenvalues')
99996 Format (1X,I4,' Infinite eigenvalue')
99995 Format (1X,I4,5X,A,F7.3,A,F7.3,A)
99994 Format (1X,'Insufficient workspace for array WORK'/' in F08XSF/', &
'ZHGEQZ')
End Program f08yxfe