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

◆ Zhpevd()

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

(Divide and conquer driver) Eigenvalues and eigenvectors of a Hermitian matrix in packed form

Purpose
This routine computes all the eigenvalues and, optionally, eigenvectors of a Hermitian matrix A in packed form. 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,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] Ap() is overwritten by values generated during the reduction to tridiagonal form. If Uplo = "U", the diagonal and first superdiagonal of the tridiagonal matrix T overwrite the corresponding elements of A. If Uplo = "L", the diagonal and first subdiagonal of T overwrite the corresponding elements of A.
[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.
= -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 Ap() is invalid.
= -5: The argument W() is invalid.
= -6: 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 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 )
Sub Ex_Zhpevd()
Const N = 3
Dim Ap(N * (N + 1) / 2) As Complex, W(N - 1) As Double, Z(N - 1, N - 1) As Complex
Dim 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)
Call Zhpevd("V", "L", N, Ap(), 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.05348849668514 0.124622388617308 1.51886610806783
Eigenvectors =
-0.449276526719113 -0 0.654793596518192 0
0.227247885813611 -0.597641779578735 0.519997178670921 -3.19846835072552E-02
0.621236109316912 -5.83009495222983E-02 0.204907317474214 -0.507777757881847
-0.607779522934083 0
0.392237107311198 0.407323787101333
-0.23846608290599 -0.503959683819116
Info = 0