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

◆ Zhpgvd()

Sub Zhpgvd ( IType As  Long,
Jobz As  String,
Uplo As  String,
N As  Long,
Ap() As  Complex,
Bp() As  Complex,
W() As  Double,
Z() As  Complex,
Info As  Long 
)

(Divide and conquer driver) Generalized eigenvalue problem of Hermitian matrices in packed form

Purpose
This routine computes all the eigenvalues, and optionally, the eigenvectors of a real generalized Hermitian-definite eigenproblem, of the form
A*x = lambda*B*x, A*Bx = lambda*x, or B*A*x = lambda*x.
Here A and B are assumed to be Hermitian, stored in packed form, and B is also positive definite.
If eigenvectors are desired, it uses a divide and conquer algorithm.
Parameters
[in]ItypeSpecifies the problem type to be solved:
= 1: A*x = lambda*B*x.
= 2: A*B*x = lambda*x.
= 3: B*A*x = lambda*x.
[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,out]Ap()Array Ap(LAp - 1) (LAp >= N(N + 1)/2)
[in] The upper or lower triangle of the Hermitian matrix A, packed columnwise in a linear array. The j-th column of A is stored in the array ap as follows.
Uplo = "U": Ap(i + j*(j + 1)/2) = Aij for 0 <= i <= j <= N - 1.
Uplo = "L": Ap((i + j*(2*N - j - 1)/2) = Aij for 0 <= j < = i <= N - 1.
[out] The contents of Ap() are destroyed.
[in,out]Bp()Array Bp(LBp - 1) (LBp >= N(N + 1)/2)
[in] The upper or lower triangle of the Hermitian positive definite matrix B, packed columnwise in a linear array. The j-th column of B is stored in the array bp as follows.
Uplo = "U": Bp(i + j*(j + 1)/2) = Bij for 0 <= i <= j <= N - 1.
Uplo = "L": Bp((i + j*(2*N - j - 1)/2) = Bij for 0 <= j < = i <= N - 1.
[out] The triangular factor U or L from the Cholesky factorization B = U^H*U or B = L*L^H, in the same storage format as B.
[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 if Jobz = "V", LZ1 >= 1, LZ2 >= 1 if Jobz = "N")
Jobz = "V": If Info = 0, Z() contains the matrix Z of eigenvectors. The eigenvectors are normalized as follows:
  Itype = 1 or 2: Z^H*B*Z = I
  Itype = 3: Z^H*inv(B)*Z = I
Jobz = "N": Z() is not referenced.
[out]Info= 0: Successful exit
= -1: The argument Itype had an illegal value (Itype < 1 or Itype > 3)
= -2: The argument Jobz had an illegal value (Jobz <> "V" nor "N")
= -3: The argument Uplo had an illegal value (Uplo <> "U" nor "L")
= -4: The argument N had an illegal value (N < 0)
= -5: The argument Ap() is invalid.
= -6: The argument Bp() is invalid.
= -7: The argument W() is invalid.
= -8: The argument Z() is invalid.
= i (0 < i <= N): Zspevd failed to converge. i off-diagonal elements of an intermediate tridiagonal form did not converge to zero.
= i (N < i <= 2n): The leading minor of order i-N of 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 matrix and B is an Hermitian positive definite matrix.
( 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 )
( 2.20 -0.11+0.93i 0.81-0.37i )
B = ( -0.11-0.93i 2.32 -0.80+0.92i )
( 0.81+0.37i -0.80-0.92i 2.29 )
Sub Ex_Zhpgvd()
Const N = 3
Dim Ap(N * (N + 1) / 2) As Complex, Bp(N * (N + 1) / 2) As Complex
Dim W(N - 1) As Double, Z(N - 1, N - 1) As Complex, Info As Long
Ap(0) = Cmplx(0.2, 0)
Ap(1) = Cmplx(-0.11, -0.93): Ap(3) = Cmplx(-0.32, 0)
Ap(2) = Cmplx(0.81, 0.37): Ap(4) = Cmplx(-0.8, -0.92): Ap(5) = Cmplx(-0.29, 0)
Bp(0) = Cmplx(2.2, 0)
Bp(1) = Cmplx(-0.11, -0.93): Bp(3) = Cmplx(2.32, 0)
Bp(2) = Cmplx(0.81, 0.37): Bp(4) = Cmplx(-0.8, -0.92): Bp(5) = Cmplx(2.29, 0)
Call Zhpgvd(1, "V", "L", N, Ap(), Bp(), 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 = -4.97466704628586 5.03789053905172E-02 0.392451765416646
Eigenvectors =
-0.819151009277443 -3.74256105252903E-17 -0.413822310464714 3.74256105252903E-17
0.320545559438499 -0.890210156692715 -0.332130735287233 1.67477550936547E-02
0.935832442766443 -6.14475107289119E-02 -0.126697019588926 0.325735727937686
-0.354935871366059 -8.42076236819031E-17
0.17251768647939 0.196424402514893
-0.125117400789647 -0.228553336347363
Info = 0