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

◆ Zgeesx_r()

Sub Zgeesx_r ( Jobvs As  String,
Sort As  String,
Sense As  String,
N As  Long,
A() As  Complex,
Sdim As  Long,
W() As  Complex,
Vs() As  Complex,
RConde As  Double,
RCondv As  Double,
Info As  Long,
IRev As  Long,
Selct() As  Long 
)

(Expert driver) Schur factorization of a complex matrix (reverse communication version)

Purpose
This routine computes for an n x n complex nonsymmetric matrix A, the eigenvalues, the Schur form T, and, optionally, the matrix of Schur vectors Z. This gives the Schur factorization A = Z*T*Z^H.

Optionally, it also orders the eigenvalues on the diagonal of the Schur form so that selected eigenvalues are at the top left; computes a reciprocal condition number for the average of the selected eigenvalues (RConde); and computes a reciprocal condition number for the right invariant subspace corresponding to the selected eigenvalues (RCondv). The leading columns of Z form an orthonormal basis for this invariant subspace.

For further explanation of the reciprocal condition numbers RConde and RCondv, see Section 4.8.1 of the LAPACK Users' Guide Third Edition (where these quantities are called s and sep respectively).

A complex matrix is in Schur form if it is upper triangular.

Zgeesx_r is the reverse communication version of Zgeesx.
Parameters
[in]Jobvs= "N": Schur vectors are not computed
= "V": Schur vectors are computed
[in]SortSpecifies whether or not to order the eigenvalues on the diagonal of the Schur form
= "N": Eigenvalues are not ordered
= "S": Eigenvalues are ordered (see Selct)
[in]SenseDetermines which reciprocal condition numbers are computed.
= 'N': None are computed.
= 'E': Computed for average of selected eigenvalues only.
= 'V': Computed for selected right invariant subspace only.
= 'B': Computed for both.
If Sense = "E", "V" or "B", Sort must equal "S"
[in]NOrder of the matrix A. (N >= 0) (If N = 0, returns without computation)
[in,out]A()Array A(LA1 - 1, LA2 - 1) (LA1 >= N, LA2 >= N)
[in] N x N matrix A.
[out] A() has been overwritten by its Schur form T.
[out]SdimSort = "N": Sdim = 0.
Sort = "S": Sdim = number of eigenvalues for which Selct(i) is true.
[out]W()Array W(LW - 1) (LW >= N)
W() contains the computed eigenvalues, in the same order that they appear on the diagonal of the output Schur form T.
[out]Vs()Array Vs(LVs1 - 1, LVs2 - 1) (LVs1 >= N, LVs2 >= N)
Jobvs = "V": Vs() contains the unitary matrix Z of Schur vectors.
Jobvs = "N": Vs() is not referenced.
[out]RCondeSense = 'E' or 'B': RConde contains the reciprocal condition number for the average of the selected eigenvalues.
Sense = 'N' or 'V': Not referenced.
[out]RCondvSense = 'V' or 'B': RCondv contains the reciprocal condition number for the selected right invariant subspace.
Sense = 'N' or 'E': Not referenced.
[out]Info= 0: Successful exit.
= -1: The argument Jobvs had an illegal value. (Jobvs <> "V" nor "N")
= -2: The argument Sort had an illegal value. (Sort <> "S" nor "N")
= -3: The argument Sense had an illegal value. (Sense <> "E", "V", "B" nor "N")
= -4: The argument N had an illegal value. (N < 0)
= -5: The argument A() is invalid.
= -7: The argument W() is invalid.
= -8: The argument Vs() is invalid.
= -13: The argument Selct() is invalid.
= i (0 < i <= N): The QR algorithm failed to compute all the eigenvalues. Elements 0 to Ilo-2 and i to N-1 of W() contain those eigenvalues which have converged. If Jobvs = "V", Vs() contains the matrix which reduces A to its partially converged Schur form.
= N+1: The eigenvalues could not be reordered because some eigenvalues were too close to separate (the problem is very ill-conditioned).
= N+2: After reordering, roundoff changed values of some complex eigenvalues so that leading eigenvalues in the Schur form no longer satisfy Selct(i) = true. This could also be caused by underflow due to scaling.
[in,out]IRevControl variable for reverse communication.
[in] Before first call, IRev should be initialized to zero. On succeeding calls, IRev should not be altered.
[out] If IRev is not zero, complete the following process and call this routine again.
= 0: Normal exit. See return code in Info
= 1: In the case of Sort = "S", to select eigenvalues to sort to the top left of the Schur form, the user should set Selct(i) (i = 0 To N-1). Decision should be made based on the values in Wr(i) and Wi(i) (real and imaginary part of the eigenvalue). Set Selct(i) = true (1) to select, or Selct(i) = false (0) not to select. Do not alter any variables other than Selct().
  Always IRev = 0 if Sort = "N".
[in]Selct()Array Selct(LSelct - 1) (LSelct >= N)
If IRev = 1, set Selct(i) to true (1) or false (0) to select eigenvalues for sorting.
Reference
LAPACK
Example Program
Compute all eigenvalues, Schur form T, and, Schur vectors 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 )
Sub Ex_Zgeesx_r()
Const N = 3
Dim A(N - 1, N - 1) As Complex, W(N - 1) As Complex
Dim Sdim As Long, Vs(N - 1, N - 1) As Complex
Dim IRev As Long, Selct(N - 1) As Long
Dim RConde As Double, RCondv As Double, 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)
IRev = 0
Do
Call Zgeesx_r("V", "S", "B", N, A(), Sdim, W(), Vs(), RConde, RCondv, Info, IRev, Selct())
If IRev = 1 Then Call Selct_r(W(), Selct())
Loop While IRev <> 0
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 "Schur form T ="
Debug.Print Creal(A(0, 0)), Cimag(A(0, 0)), Creal(A(0, 1)), Cimag(A(0, 1))
Debug.Print Creal(A(1, 0)), Cimag(A(1, 0)), Creal(A(1, 1)), Cimag(A(1, 1))
Debug.Print Creal(A(2, 0)), Cimag(A(2, 0)), Creal(A(2, 1)), Cimag(A(2, 1))
Debug.Print Creal(A(0, 2)), Cimag(A(0, 2))
Debug.Print Creal(A(1, 2)), Cimag(A(1, 2))
Debug.Print Creal(A(2, 2)), Cimag(A(2, 2))
Debug.Print "Schur vectors ="
Debug.Print Creal(Vs(0, 0)), Cimag(Vs(0, 0)), Creal(Vs(0, 1)), Cimag(Vs(0, 1))
Debug.Print Creal(Vs(1, 0)), Cimag(Vs(1, 0)), Creal(Vs(1, 1)), Cimag(Vs(1, 1))
Debug.Print Creal(Vs(2, 0)), Cimag(Vs(2, 0)), Creal(Vs(2, 1)), Cimag(Vs(2, 1))
Debug.Print Creal(Vs(0, 2)), Cimag(Vs(0, 2))
Debug.Print Creal(Vs(1, 2)), Cimag(Vs(1, 2))
Debug.Print Creal(Vs(2, 2)), Cimag(Vs(2, 2))
Debug.Print "Rconde =", RConde, "Rcondv =", RCondv
Debug.Print "Sdim =", Sdim, "Info =", Info
End Sub
Sub Selct_r(W() As Complex, Selct() As Long)
Const N = 3
Dim I As Long
For I = 0 To N - 1
Selct(I) = 0
If Cimag(W(I)) <> 0 Then Selct(I) = 1
Next
End Sub
Example Results
Eigenvalues =
-1.15894122423918 -0.50662892448174 1.05593587167591 0.900255855387815
0.21300535256327 1.29637306909393
Schur form T =
-1.15894122423918 -0.50662892448174 2.31358655627147E-02 -0.442808752291521
0 0 1.05593587167591 0.900255855387815
0 0 0 0
-0.644484909898823 -0.733094546116673
0.379301413619788 -0.286520422490734
0.21300535256327 1.29637306909393
Schur vectors =
-0.474826946245658 0.464530398931381 -0.103329315153953 0.628092734605153
-0.39444507925059 0.539925475846714 -9.30826818180923E-02 -0.290418461635993
0.264837176182039 -0.203729501266495 -0.367753983153771 0.605452152301986
1.03227229675376E-02 0.391748503946406
2.12814186266949E-02 -0.67781516115713
0.349266221164391 -0.514347515136026
Rconde = 1 Rcondv = 2.76522085257846
Sdim = 3 Info = 0