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

◆ Zhbgv()

Sub Zhbgv ( Jobz As  String,
Uplo As  String,
N As  Long,
Ka As  Long,
Kb As  Long,
Ab() As  Complex,
Bb() As  Complex,
W() As  Double,
Z() As  Complex,
Info As  Long 
)

(Simple driver) Generalized eigenvalue problem of Hermitian band matrices

Purpose
This routine computes all the eigenvalues, and optionally, the eigenvectors of a complex generalized Hermitian-definite banded eigenproblem, of the form
Ax = λBx.
Here A and B are assumed to be Hermitian and banded, and B is also positive definite.
Parameters
[in]Jobz= "N": Compute eigenvalues only.
= "V": Compute eigenvalues and eigenvectors.
[in]Uplo= "U": Upper triangles of A and B are stored.
= "L": Lower triangles of A and B are stored.
[in]NOrder of the matrices A and B. (N >= 0) (If N = 0, returns without computation)
[in]KaNumber of super-diagonals of the matrix A if Uplo = "U" or the number of sub-diagonals if Uplo = "L". (ka >= 0)
[in]KbNumber of super-diagonals of the matrix B if Uplo = "U" or the number of sub-diagonals if Uplo = "L". (kb >= 0)
[in,out]Ab()Array Ab(LAb1 - 1, LAb2 - 1) (LAb1 >= Ka + 1, LAb2 >= N)
[in] N x N Hermitian band matrix A in Ka+1 x N symmetric band matrix form. Upper or lower part is to be stored in accordance with Uplo.
[out] The contents of Ab() are destroyed.
[in,out]Bb()Array Bb(LBb1 - 1, LBb2 - 1) (LBb1 >= Kb + 1, LBb2 >= N)
[in] N x N Hermitian positive definite band matrix B in Kb+1 x N symmetric band matrix form. Upper or lower part is to be stored in accordance with Uplo.
[out] The factor S from the split Cholesky factorization B = S^H*S, as returned by Zpbstf.
[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 matrix Z of eigenvectors, with the i-th column of Z holding the eigenvector associated with W(i). The eigenvectors are normalized so that Z^H*B*Z = I.
Jobz = "N": Z() is not referenced.
[out]Info= 0: Successful exit.
= -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 Ka had an illegal value. (Ka < 0)
= -5: The argument Kb had an illegal value. (Kb < 0)
= -6: The argument Ab() is invalid.
= -7: The argument Bb() is invalid.
= -8: The argument W() is invalid.
= -9: The argument Z() is invalid.
= i (0 < i <= N): The algorithm failed to converge. i off-diagonal elements of an intermediate tridiagonal form did not converge to zero.
= i (i > N): Zpbstf returned Info = i-N. B is not positive definite. The factorization of B could not be completed and no eigenvalues or eigenvectors were computed.
Reference
LAPACK
Example Program
Compute the eigenvalues and the eigenvectors of a generalized Hermitian-definite eigenproblem of the form Ax = λBx, where A is an Hermitian band matrix and B is an Hermitian positive definite band matrix.
( 0.20 -0.11+0.93i 0 )
A = ( -0.11-0.93i -0.32 -0.80+0.92i )
( 0 -0.80-0.92i -0.29 )
( 2.20 -0.11+0.93i 0 )
B = ( -0.11-0.93i 2.32 -0.80+0.92i )
( 0 -0.80-0.92i 2.29 )
Sub Ex_Zhbgv()
Const N = 3, Ka = 1, Kb = 1
Dim Ab(Ka, N - 1) As Complex, Bb(Kb, N - 1) As Complex
Dim W(N - 1) As Double, Z(N - 1, N - 1) As Complex, Info As Long
Ab(0, 0) = Cmplx(0.2): Ab(0, 1) = Cmplx(-0.32): Ab(0, 2) = Cmplx(-0.29)
Ab(1, 0) = Cmplx(-0.11, -0.93): Ab(1, 1) = Cmplx(-0.8, -0.92)
Bb(0, 0) = Cmplx(2.2): Bb(0, 1) = Cmplx(2.32): Bb(0, 2) = Cmplx(2.29)
Bb(1, 0) = Cmplx(-0.11, -0.93): Bb(1, 1) = Cmplx(-0.8, -0.92)
Call Zhbgv("V", "L", N, Ka, Kb, Ab(), Bb(), 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 = -2.33466883563969 4.53015245998351E-03 0.35977634455495
Eigenvectors =
0.47826114359381 -6.39634991743266E-18 0.507837765924615 -8.10231908112231E-19
9.59938458849389E-02 0.811584333390847 1.21596344669029E-02 0.102804182311088
-0.441771484124976 0.486432071889564 0.281208537371776 -0.309637123223848
0.332163577636529 2.56485488839366E-18
-3.84923101537441E-02 -0.325434985845291
-0.154385502431493 0.169992999811227
Info = 0