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

◆ Zhbevd()

Sub Zhbevd ( Jobz As  String,
Uplo As  String,
N As  Long,
Kd As  Long,
Ab() As  Complex,
W() As  Double,
Z() As  Complex,
Info As  Long 
)

(Divide and conquer driver) Eigenvalues and eigenvectors of a Hermitian band matrix

Purpose
This routine computes all the eigenvalues and, optionally, eigenvectors of a Hermitian band matrix A. If only eigenvalues are desired, it uses a QL or QR method. If eigenvectors are also desired, it uses a divide and conquer algorithm.
Parameters
[in]Jobz= "N": Compute eigenvalues only.
= "V": Compute eigenvalues and eigenvectors.
[in]Uplo= "U": Upper triangle of A is stored.
= "L": Lower triangle of A is stored.
[in]NOrder of the matrix A. (N >= 0) (If N = 0, returns without computation)
[in]KdNumber of superdiagonals of the matrix A if Uplo = "U" or number of subdiagonals if Uplo = "L". (Kd >= 0)
[in,out]Ab()Array Ab(LAb1 - 1, LAb2 - 1) (LAb1 >= Kd + 1, LAb2 >= N)
[in] The upper or lower triangle of the Hermitian band matrix A, stored in the first Kd + 1 columns of the array. The j-th column of A is stored in the j-th column of the array Ab() as follows.
Uplo = "U": Ab(Kd + i - j, j) = Aij for max(0, j - Kd - 1) <= i <= j <= N - 1.
Uplo = "L": Ab(i - j, j) = Aij for 0 <= j <= i <= min(N - 1, j + Kd - 1).
[out] Ab() is overwritten by values generated during the reduction to tridiagonal form. If Uplo = "U", the first superdiagonal and the diagonal of the tridiagonal matrix T are returned in rows Kd and Kd + 1 of Ab(). If Uplo = "L", the diagonal and first subdiagonal of T are returned in the first two rows of Ab().
[out]W()Array W(LW - 1) (LW >= N)
If Info = 0, the eigenvalues in ascending order.
[out]Z()Array Z(LZ1 - 1, LZ2 - 1) (LZ1 >= N, LZ2 >= N)
Jobz = "V": If Info = 0, Z() contains the orthonormal eigenvectors of the matrix A, with the i-th column of Z() holding the eigenvector associated with W(i).
Jobz = "N": Z() is not referenced.
[out]Info= 0: Successful exit__N = -1: The argument Jobz had an illegal value. (Jobz <> "V" nor "N")
= -2: The argument Uplo had an illegal value. (Uplo <> "U" nor "L")
= -3: The argument N had an illegal value. (N < 0)
= -4: The argument Kd had an illegal value. (Kd < 0)
= -5: The argument Ab() is invalid.
= -6: The argument W() is invalid.
= -7: The argument Z() is invalid.
= i > 0: The algorithm failed to converge; i off-diagonal elements of an intermediate tridiagonal form did not converge to zero
Reference
LAPACK
Example Program
Compute all eigenvalues and eigenvectors of the Hermitian band matrix A, where
( 2.20 -0.32-0.81i 0 )
A = ( -0.32+0.81i 2.11 0.37+0.80i )
( 0 0.37-0.80i 2.93 )
Sub Ex_Zhbev()
Const N = 3, Kd = 1
Dim Ab(Kd, N - 1) As Complex, W(N - 1) As Double, Z(N - 1, N - 1) As Complex
Dim Info As Long
Ab(0, 0) = Cmplx(2.2, 0): Ab(0, 1) = Cmplx(2.11, 0): Ab(0, 2) = Cmplx(2.93, 0)
Ab(1, 0) = Cmplx(-0.32, 0.81): Ab(1, 1) = Cmplx(0.37, -0.8)
Call Zhbev("V", "L", N, Kd, Ab(), W(), Z(), Info)
Debug.Print "Eigenvalues =", W(0), W(1), W(2)
Debug.Print "Eigenvectors ="
Debug.Print Creal(Z(0, 0)), Cimag(Z(0, 0)), Creal(Z(0, 1)), Cimag(Z(0, 1))
Debug.Print Creal(Z(1, 0)), Cimag(Z(1, 0)), Creal(Z(1, 1)), Cimag(Z(1, 1))
Debug.Print Creal(Z(2, 0)), Cimag(Z(2, 0)), Creal(Z(2, 1)), Cimag(Z(2, 1))
Debug.Print Creal(Z(0, 2)), Cimag(Z(0, 2))
Debug.Print Creal(Z(1, 2)), Cimag(Z(1, 2))
Debug.Print Creal(Z(2, 2)), Cimag(Z(2, 2))
Debug.Print "Info =", Info
End Sub
Example Results
Eigenvalues = 1.04283948355918 2.52504447979701 3.67211603664382
Eigenvectors =
-0.563395195782213 0 0.745522345299636 0
-0.275043343741226 0.696203463844978 -0.102234588437164 0.258781301981572
-0.241207215775279 -0.253094504921304 -0.417819329339414 -0.438410500970378
-0.356065002532476 0
0.221139195914327 -0.55975858965814
-0.493164614651588 -0.51746898859873
Info = 0