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

◆ Zsteqr()

Sub Zsteqr ( Compz As  String,
N As  Long,
D() As  Double,
E() As  Double,
Z() As  Complex,
Info As  Long 
)

Eigenvalues and eigenvectors of a symmetric tridiagonal matrix to which a Hermitian matrix was reduced (QL or QR method)

Purpose
This routine computes all eigenvalues and, optionally, eigenvectors of a symmetric tridiagonal matrix to which a Hermitian matrix was reduced using the implicit QL or QR method. The eigenvectors of a full or band Hermitian matrix can also be found if Zhetrd, Zhptrd or Zhbtrd has been used to reduce this matrix to tridiagonal form.
Parameters
[in]Compz= "N": Compute eigenvalues only.
= "V": Compute eigenvalues and eigenvectors of the original Hermitian matrix. On entry, Z() must contain the unitary matrix used to reduce the original matrix to tridiagonal form.
= "I": Compute eigenvalues and eigenvectors of the tridiagonal matrix. Z() is initialized to the identity matrix.
[in]NOrder of the matrix. (N >= 0) (If N = 0, returns without computation)
[in,out]D()Array D(LD - 1) (LD >= N)
[in] The diagonal elements of the tridiagonal matrix.
[out] If Info = 0, the eigenvalues in ascending order.
[in,out]E()Array E(LE - 1) (LE >= N - 1)
[in] The (N - 1) subdiagonal elements of the tridiagonal matrix.
[out] E() has been destroyed.
[in,out]Z()Array Z(LZ1 - 1, LZ2 - 1) (LZ1 >= N, LZ2 >= N)
[in] If Compz = "V", then Z() contains the unitary matrix used in the reduction to tridiagonal form.
[out] If Info = 0, then if Compz = "V", Z() contains the orthonormal eigenvectors of the original Hermitian matrix, and if Compz = "I", Z() contains the orthonormal eigenvectors of the symmetric tridiagonal matrix. If Compz = "N", then Z() is not referenced.
[out]Info= 0: Successful exit.
= -1: The argument Compz had an illegal value. (Compz <> "N", "V" nor "I")
= -2: The argument N had an illegal value. (N < 0)
= -3: The argument D() is invalid.
= -4: The argument E() is invalid.
= -5: The argument Z() is invalid.
= i > 0: The algorithm has failed to find all the eigenvalues in a total of 30*N iterations. i elements of E() have not converged to zero. On exit, D() and E() contain the elements of a symmetric tridiagonal matrix which is unitarily similar to the original matrix.
Reference
LAPACK
Example Program
Compute all eigenvalues and eigenvectors of the Hermitian matrix A, where
( 0.20 -0.11+0.93i 0.81-0.37i )
A = ( -0.11-0.93i -0.32 -0.80+0.92i )
( 0.81+0.37i -0.80-0.92i -0.29 )
Reduces to real tridiagonal form by Zhetrd, then Zungtr and Zsteqr are applied.
Sub Ex_Zhetrd_Zsteqr()
Const N = 3
Dim A(N - 1, N - 1) As Complex, Info As Long
Dim D(N - 1) As Double, E(N - 2) As Double, Tau(N - 2) As Complex
A(0, 0) = Cmplx(0.2, 0)
A(1, 0) = Cmplx(-0.11, -0.93): A(1, 1) = Cmplx(-0.32, 0)
A(2, 0) = Cmplx(0.81, 0.37): A(2, 1) = Cmplx(-0.8, -0.92): A(2, 2) = Cmplx(-0.29, 0)
Call Zhetrd("L", N, A(), D(), E(), Tau(), Info)
If Info <> 0 Then
Debug.Print "Error in Zhetrd: Info =", Info
Exit Sub
End If
Call Zungtr("L", N, A(), Tau(), Info)
If Info <> 0 Then
Debug.Print "Error in Zungtr: Info =", Info
Exit Sub
End If
Call Zsteqr("V", N, D(), E(), A(), Info)
If Info <> 0 Then
Debug.Print "Error in Zsterf: Info =", Info
Exit Sub
End If
Debug.Print "Eigenvalues =", D(0), D(1), D(2)
Debug.Print "Eigenvectors ="
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))
End Sub
Example Results
Eigenvalues = -2.05348849668514 0.124622388617308 1.51886610806783
Eigenvectors =
-0.449276526719113 -0 0.654793596518192 0
0.227247885813611 -0.597641779578735 0.519997178670921 -3.19846835072552E-02
0.621236109316913 -5.83009495222984E-02 0.204907317474214 -0.507777757881847
-0.607779522934083 0
0.392237107311198 0.407323787101333
-0.23846608290599 -0.503959683819116