XLPack 6.1
Excel VBA Numerical Library Reference Manual
Loading...
Searching...
No Matches

◆ Zggevx()

Sub Zggevx ( Balanc As  String,
Jobvl As  String,
Jobvr As  String,
Sense As  String,
N As  Long,
A() As  Complex,
B() As  Complex,
Alpha() As  Complex,
Beta() As  Complex,
Vl() As  Complex,
Vr() As  Complex,
Ilo As  Long,
Ihi As  Long,
LScale() As  Double,
RScale() As  Double,
AbNrm As  Double,
BbNrm As  Double,
RConde() As  Double,
RCondv() As  Double,
Info As  Long 
)

(Expert driver) Generalized eigenvalue problem of complex matrices

Purpose
This routine computes for a pair of n x n complex nonsymmetric matrices (A, B), the generalized eigenvalues, and optionally, the left and/or right generalized eigenvectors.

Optionally, it also computes a balancing transformation to improve the conditioning of the eigenvalues and eigenvectors (Ilo, Ihi, Lscale, Rrscale, AbNrm, and BbNrm), reciprocal condition numbers for the eigenvalues (RConde), and reciprocal condition numbers for the right eigenvectors (RCondv).

A generalized eigenvalue for a pair of matrices (A, B) is a scalar λ or a ratio α/β = λ, such that A - λ*B is singular. It is usually represented as the pair (α, β), as there is a reasonable interpretation for β = 0, and even for both being zero.

The right generalized eigenvector v(j) corresponding to the generalized eigenvalue λ(j) of (A, B) satisfies

A * v(j) = λ(j) * B * v(j)

The left generalized eigenvector u(j) corresponding to the generalized eigenvalue λ(j) of (A, B) satisfies

u(j)^H * A = λ(j) * u(j)^H * B

where u(j)^H is the conjugate-transpose of u(j).

Parameters
[in]BalancSpecifies the balance option to be performed.
= "N": Do not diagonally scale or permute.
= "P": Permute only.
= "S": Scale only.
= "B": Both permute and scale.
Computed reciprocal condition numbers will be for the matrices after permuting and/or balancing. Permuting does not change condition numbers (in exact arithmetic), but balancing does.
[in]JobVl= "N": Do not compute the left generalized eigenvectors.
= "V": Compute the left generalized eigenvectors.
[in]JobVr= "N": Do not compute the right generalized eigenvectors.
= "V": Compute the right generalized eigenvectors.
[in]SenseDetermines which reciprocal condition numbers are computed.
= "N": None are computed.
= "E": Computed for eigenvalues only.
= "V": Computed for right eigenvectors only.
= "B": Computed for eigenvalues and right eigenvectors.
[in]NOrder of the matrices A, B, VL and VR. (N >= 0) (If N = 0, returns without computation)
[in,out]A()Array A(LA1 - 1, LA2 - 1) (LA1 >= N, LA2 >= N)
[in] Matrix A in the pair (A, B).
[out] A() has been overwritten. If jobvl = "V" or jobvr = "V" or both, then A() contains the first part of the complex Schur form of the "balanced" versions of the input A and B.
[in,out]B()Array B(LB1 - 1, LB2 - 1) (LB1 >= N, LB2 >= N)
[in] Matrix B in the pair (A, B).
[out] B() has been overwritten. If jobvl = "V" or jobvr = "V" or both, then B() contains the second part of the complex Schur form of the "balanced" versions of the input A and B.
[out]Alpha()Array Alpha(LAlpha - 1) (LAlpha >= N)
[out]Beta()Array Beta(LBeta - 1) (LBeta >= N)
Alphar(j)/Beta(j), j = 0, ..., N-1, will be the generalized eigenvalues.

Note: The quotients Alpha(j)/Beta(j) may easily over- or underflow, and Beta(j) may even be zero. Thus, the user should avoid naively computing the ratio α/β. However, Alpha will be always less than and usually comparable with norm(A) in magnitude, and Beta always less than and usually comparable with norm(B).
[out]Vl()Array Vl(LVl1 - 1, LVl2 - 1) (LVl1 >= N, LVl2 >= N)
Jobvl = "V": The left generalized eigenvectors u(j) are stored one after another in the columns of Vl(), in the same order as their eigenvalues. Each eigenvector is scaled so the largest component has |real part| + |imaginary part| = 1.
Jobvl = "N": Not referenced.
[out]Vr()Array Vr(LVr1 - 1, LVr2 - 1) (LVr1 >= N, LVr2 >= N)
jobvr = "V": The right generalized eigenvectors v(j) are stored one after another in the columns of Vr() in the same order as their eigenvalues. Each eigenvector is scaled so the largest component has |real part| + |imaginary part| = 1.
jobvr = "N": Not referenced.
[out]IloIlo and Ihi are integer values such that on exit A(i, j) = 0 and B(i, j) = 0 if i > j and j = 0, ..., Ilo-2 or i = Ihi, ..., N-1.
If Balanc = "N" or "S", Ilo = 1 and Ihi = N.
[out]Ihi
[out]LScale()Array LScale(LLScale - 1) (LLScale >= N)
Details of the permutations and scaling factors applied to the left side of A and B. If Pl(j) is the index of the row interchanged with row j, and Dl(j) is the scaling factor applied to row j, then
  LScale(j) = Pl(j) for j = 0, ..., Ilo-2
    = Dl(j) for j = Ilo-1, ..., Ihi-1
    = Pl(j) for j = Ihi, ..., N-1
The order in which the interchanges are made is N-1 to Ihi, then 0 to Ilo-2.
[out]RScale()Array RScale(LRScale - 1) (LRScale >= N)
Details of the permutations and scaling factors applied to the right side of A and B. If Pr(j) is the index of the column interchanged with column j, and Dr(j) is the scaling factor applied to column j, then
  RScale(j) = Pr(j) for j = 0, ..., Ilo-2
    = Dr(j) for j = Ilo-1, ..., Ihi-1
    = Pr(j) for j = Ihi, ..., N-1
The order in which the interchanges are made is N-1 to Ihi, then 0 to Ilo-2.
[out]AbNrmOne-norm of the balanced matrix A.
[out]BbNrmOne-norm of the balanced matrix B.
[out]RConde()Array RConde(LRConde - 1) (LRConde >= N)
Sense = "E" or "B": The reciprocal condition numbers of the eigenvalues, stored in consecutive elements of the array.
If Sense = "N" or "V": RConde() is not referenced.
[out]RCondv()Array RCondv(LRCondv - 1) (LRCondv >= N)
Sense = "V" or "B": The estimated reciprocal condition numbers of the eigenvectors, stored in consecutive elements of the array. If the eigenvalues cannot be reordered to compute RCondv(j), RCondv(j) is set to 0. This can only occur when the true value would be very small anyway.
If Sense = "N" or "V": RCondv() is not referenced.
[out]Info= 0: Successful exit.
= -1: The argument Balanc had an illegal value. (Balanc <> "N", "P", "S" nor "B")
= -2: The argument Jobvl had an illegal value. (Jobvl <> "V" nor "N")
= -3: The argument Jobvr had an illegal value. (Jobvr <> "V" nor "N")
= -4: The argument Sense had an illegal value. (Sense <> "N", "E", "V" nor "B")
= -5: The argument N had an illegal value. (N < 0)
= -6: The argument A() is invalid.
= -7: The argument B() is invalid.
= -8: The argument Alphr() is invalid.
= -9: The argument Beta() is invalid.
= -10: The argument Vl() is invalid.
= -11: The argument Vr() is invalid.
= -14: The argument LScale() is invalid.
= -15: The argument RScale() is invalid.
= -18: The argument RConde() is invalid.
= -19: The argument RCondv() is invalid.
= i (0 < i <= N): The QZ iteration failed. No eigenvectors have been calculated, but Alpha(j) and Beta(j) should be correct for j = i, ..., N-1.
= N+1: Other than QZ iteration failed in Zhgeqz.
= N+2: Error return from Ztgevc.
Reference
LAPACK
Example Program
Compute for a pair of matrices (A, B) the generalized eigenvalues and the left and right generalized eigenvectors, where
( 0.2-0.11i -0.93-0.32i 0.81+0.37i )
A = ( -0.8-0.92i -0.29+0.86i 0.64+0.51i )
( 0.71+0.59i -0.15+0.19i 0.2+0.94i )
( 0.57-0.91i -0.28-0.45i 0.25+0.91i )
B = ( 0.83-0.46i 0.63-0.19i -0.69+0.09i )
( 0.24-1.33i -0.56-0.67i 0.9+1.25i )
Sub Ex_Zggevx()
Const N = 3
Dim A(N - 1, N - 1) As Complex, B(N - 1, N - 1) As Complex
Dim Alpha(N - 1) As Complex, Beta(N - 1) As Complex
Dim Vl(N - 1, N - 1) As Complex, Vr(N - 1, N - 1) As Complex, Info As Long
Dim Ilo As Long, Ihi As Long, LScale(N - 1) As Double, RScale(N - 1) As Double
Dim AbNrm As Double, BbNrm As Double
Dim RConde(N - 1) As Double, RCondv(N - 1) As Double
A(0, 0) = Cmplx(0.2, -0.11): A(0, 1) = Cmplx(-0.93, -0.32): A(0, 2) = Cmplx(0.81, 0.37)
A(1, 0) = Cmplx(-0.8, -0.92): A(1, 1) = Cmplx(-0.29, 0.86): A(1, 2) = Cmplx(0.64, 0.51)
A(2, 0) = Cmplx(0.71, 0.59): A(2, 1) = Cmplx(-0.15, 0.19): A(2, 2) = Cmplx(0.2, 0.94)
B(0, 0) = Cmplx(0.57, -0.91): B(0, 1) = Cmplx(-0.28, -0.45): B(0, 2) = Cmplx(0.25, 0.91)
B(1, 0) = Cmplx(0.83, -0.46): B(1, 1) = Cmplx(0.63, -0.19): B(1, 2) = Cmplx(-0.69, 0.09)
B(2, 0) = Cmplx(0.24, -1.33): B(2, 1) = Cmplx(-0.56, -0.67): B(2, 2) = Cmplx(0.9, 1.25)
Call Zggevx("N", "V", "V", "N", N, A(), B(), Alpha(), Beta(), Vl(), Vr(), Ilo, Ihi, LScale(), RScale(), AbNrm, BbNrm, RConde(), RCondv(), Info)
Debug.Print "Eigenvalues ="
Debug.Print Creal(Cdiv(Alpha(0), Beta(0))), Cimag(Cdiv(Alpha(0), Beta(0))),
Debug.Print Creal(Cdiv(Alpha(1), Beta(1))), Cimag(Cdiv(Alpha(1), Beta(1)))
Debug.Print Creal(Cdiv(Alpha(2), Beta(2))), Cimag(Cdiv(Alpha(2), Beta(2)))
Debug.Print "Eigenvectors (L) ="
Debug.Print Creal(Vl(0, 0)), Cimag(Vl(0, 0)), Creal(Vl(0, 1)), Cimag(Vl(0, 1))
Debug.Print Creal(Vl(1, 0)), Cimag(Vl(1, 0)), Creal(Vl(1, 1)), Cimag(Vl(1, 1))
Debug.Print Creal(Vl(2, 0)), Cimag(Vl(2, 0)), Creal(Vl(2, 1)), Cimag(Vl(2, 1))
Debug.Print Creal(Vl(0, 2)), Cimag(Vl(0, 2))
Debug.Print Creal(Vl(1, 2)), Cimag(Vl(1, 2))
Debug.Print Creal(Vl(2, 2)), Cimag(Vl(2, 2))
Debug.Print "Eigenvectors (R) ="
Debug.Print Creal(Vr(0, 0)), Cimag(Vr(0, 0)), Creal(Vr(0, 1)), Cimag(Vr(0, 1))
Debug.Print Creal(Vr(1, 0)), Cimag(Vr(1, 0)), Creal(Vr(1, 1)), Cimag(Vr(1, 1))
Debug.Print Creal(Vr(2, 0)), Cimag(Vr(2, 0)), Creal(Vr(2, 1)), Cimag(Vr(2, 1))
Debug.Print Creal(Vr(0, 2)), Cimag(Vr(0, 2))
Debug.Print Creal(Vr(1, 2)), Cimag(Vr(1, 2))
Debug.Print Creal(Vr(2, 2)), Cimag(Vr(2, 2))
Debug.Print "Info =", Info
End Sub
Example Results
Eigenvalues =
-0.4784814787767 -0.640760182519056 1.62433774044009 1.10642263894432
-0.149178317709927 5.63446258373312
Eigenvectors (L) =
-0.488182728920006 0.511817271079994 0.112214636564846 -0.78086108170552
-0.493389319144031 1.33311637129139E-02 -0.132533171028514 -0.347190877300084
0.339735049171677 -6.82051937200691E-02 0.672543628409034 0.327456371590966
0.902635460243872 9.73645397561283E-02
-0.178648471173719 0.129164561360569
-0.730361156069673 7.60898456031052E-02
Eigenvectors (R) =
-0.573248979253811 -0.426751020746189 0.644105768156504 -0.298230968832631
-0.249087460228498 -9.31247915124554E-02 -0.701765691258405 -0.298234308741595
0.271914164828682 -0.477707190075455 0.274425774522266 -0.280815941661082
2.08352227991442E-02 2.31726206010056E-02
-0.737220272842649 -0.262779727157351
-0.474367740415068 -4.82054262401725E-02
Info = 0