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

◆ Ztrevc3()

Sub Ztrevc3 ( Side As  String,
Howmny As  String,
Selct() As  Boolean,
N As  Long,
T() As  Complex,
Vl() As  Complex,
Vr() As  Complex,
Mm As  Long,
M As  Long,
Info As  Long 
)

Eigenvectors of complex triangular matrix of Schur factorization

Purpose
This routine computes some or all of the right and/or left eigenvectors of a complex upper triangular matrix T. Matrices of this type are produced by the Schur factorization of a complex general matrix: A = Q*T*Q^H, as computed by Zhseqr.

The right eigenvector x and the left eigenvector y of T corresponding to an eigenvalue w are defined by:
T*x = w*x, (y^H)*T = w*(y^H)
where y^H denotes the conjugate transpose of the vector y. The eigenvalues are not input to this routine, but are read directly from the diagonal blocks of T.

This routine returns the matrices X and/or Y of right and left eigenvectors of T, or the products Q*X and/or Q*Y, where Q is an input matrix. If Q is the unitary factor that reduces a matrix A to Schur form T, then Q*X and Q*Y are the matrices of right and left eigenvectors of A.

This uses a Level 3 BLAS version of the back transformation.
Parameters
[in]Side= "R": Compute right eigenvectors only.
= "L": Compute left eigenvectors only.
= "B": Compute both right and left eigenvectors.
[in]Howmny= "A": Compute all right and/or left eigenvectors.
= "B": Compute all right and/or left eigenvectors, backtransformed by the matrices in Vl() and/or Vr().
= "S": Compute selected right and/or left eigenvectors, as indicated by the logical array Selct().
[in,out]Selct()Array Selct(LSelct - 1) (LSelct >= N)
If Howmny = "S", Selct() specifies the eigenvectors to be computed. The eigenvector corresponding to the j-th eigenvaalue is computed if Selct(j) = True.
Not referenced if Howmny = "A" or "B".
[in]NOrder of the matrix A. (N >= 0) (If N = 0, returns without computation)
[in]T()Array T(LT1 - 1, LT2 - 1) (LT1 >= N, LT2 >= N)
The upper triangular matrix T. T() is modified, but restored on exit.
[in,out]Vl()Array Vl(LVl1 - 1, LVl2 - 1) (LVl1 >= N, LVl2 >= MM)
[in] If Side = "L" or "B" and Howmny = "B", Vl() must contain an N x N matrix Q (usually the unitary matrix Q of Schur vectors returned by Zhseqr).
[out] If Side = "L" or "B", Vl() contains:
if Howmny = "A", the matrix Y of left eigenvectors of T;
if Howmny = "B", the matrix Q*Y;
if Howmny = "S", the left eigenvectors of T specified by Selct(), stored consecutively in the columns of Vl(), in the same order as their eigenvalues.
Not referenced if Side = "R".
[in,out]Vr()Array Vr(LVr1 - 1, LVr2 - 1) (LVr1 >= N, LVr2 >= MM)
[in] If Side = "R" or "B" and Howmny = "B", Vr() must contain an N x N matrix Q (usually the unitary matrix Q of Schur vectors returned by Zhseqr).
[out] If Side = "R" or "B", Vr() contains:
if Howmny = "A", the matrix X of right eigenvectors of T;
if Howmny = "B", the matrix Q*X;
if Howmny = "S", the right eigenvectors of T specified by Selct(), stored consecutively in the columns of Vr(), in the same order as their eigenvalues.
Not referenced if Side = "L".
[in]MMThe number of columns in the arrays Vl() and/or Vr(). (MM >= M)
[out]MThe number of columns in the arrays Vl() and/or Vr() actually used to store the eigenvectors.
If Howmny = "A" or "B", M is set to N.
Each selected eigenvector occupies one column.
[out]Info= 0: Successful exit.
= -1: The argument Side had an illegal value. (Side <> "R", "L" nor "B")
= -2: The argument Howmny had an illegal value. (Hownmy <> "A", "B" nor "S")
= -3: The argument Selct() is invalid.
= -4: The argument N had an illegal value. (N < 0)
= -5: The argument T() is invalid.
= -6: The argument Vl() is invalid.
= -7: The argument Vr() is invalid.
= -8: The argument MM had an illegal value. (MM < M)
Further Details
The algorithm used in this program is basically backward (forward) substitution, with scaling to make the the code robust against possible overflow.

Each eigenvector is normalized so that the element of largest magnitude has magnitude 1; here the magnitude of a complex number (x,y) is taken to be |x| + |y|.
Reference
LAPACK
Example Program
Compute all eigenvalues and eigenvectors of the general matrix A, where
( 0.20-0.11i -0.93-0.32i 0.81+0.37i )
A = ( -0.80-0.92i -0.29+0.86i 0.64+0.51i )
( 0.71+0.59i -0.15+0.19i 0.20+0.94i )
Reduces to Hessenberg form by Zgehrd, then computes eigenvalues and Schur form by Zhseqr and Zunghr. Ztrevc3 computes the eigenvectors from Schur form.
Sub Ex_Zgehrd_Zhseqr_Ztrevc3()
Const N = 3
Dim A(N - 1, N - 1) As Complex, Tau(N - 2) As Complex
Dim W(N - 1) As Complex, Selct() As Boolean
Dim Vl(N - 1, N - 1) As Complex, Vr(N - 1, N - 1) As Complex, M As Long
Dim Ilo As Long, Ihi As Long, I As Long, J As Long, Info As Long
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)
Ilo = 1: Ihi = N
Call Zgehrd(N, Ilo, Ihi, A(), Tau(), Info)
If Info <> 0 Then
Debug.Print "Error in Zgehrd: Info =", Info
Exit Sub
End If
For I = 0 To N - 1
For J = 0 To N - 1
Vr(I, J) = A(I, J)
Next
Next
Call Zunghr(N, Ilo, Ihi, Vr(), Tau(), Info)
If Info <> 0 Then
Debug.Print "Error in Zunghr: Info =", Info
Exit Sub
End If
Call Zhseqr("S", "V", N, Ilo, Ihi, A(), W(), Vr(), Info)
If Info <> 0 Then
Debug.Print "Error in Zhseqr: Info =", Info
Exit Sub
End If
For I = 0 To N - 1
For J = 0 To N - 1
Vl(I, J) = Vr(I, J)
Next
Next
Call Ztrevc3("B", "B", Selct(), N, A(), Vl(), Vr(), N, M, Info)
If Info <> 0 Then
Debug.Print "Error in Dtrevc3: Info =", Info
Exit Sub
End If
Debug.Print "Eigenvalues ="
Debug.Print Creal(W(0)), Cimag(W(0)), Creal(W(1)), Cimag(W(1))
Debug.Print Creal(W(2)), Cimag(W(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 "M =", M
End Sub
Example Results
Eigenvalues =
-1.15894122423918 -0.50662892448174 1.05593587167591 0.900255855387815
0.21300535256327 1.29637306909393
Eigenvectors (L) =
-0.36286784799871 0.63713215200129 -0.144564860055844 0.855435139944156
-0.395771083048871 0.240186600504172 -1.15502382771539E-02 -0.649951770460259
0.434572937991399 -0.277594817887723 -0.144369992549788 0.399622008123156
1.19529397618877E-02 0.453615415642407
2.46422882501396E-02 -0.784859171023358
0.404424115184401 -0.595575884815599
Eigenvectors (R) =
-0.505480633843522 0.494519366156478 4.45520906484036E-03 0.657348688695353
-0.419909506510805 0.574781768215114 1.90776326854836E-02 -0.276338131107688
0.28193442840661 -0.216881788717049 -0.418424064044568 0.581575935955432
0.105185244310007 -0.110887166536361
0.164796997542067 -0.65350282278796
0.340224561176925 -0.659775438823075
M = 3