|
◆ Zhptrd()
Sub Zhptrd |
( |
Uplo As |
String, |
|
|
N As |
Long, |
|
|
Ap() As |
Complex, |
|
|
D() As |
Double, |
|
|
E() As |
Double, |
|
|
Tau() As |
Complex, |
|
|
Info As |
Long |
|
) |
| |
Reduces a real Hermitian matrix stored in packed form to tridiagonal form
- Purpose
- This routine reduces a Hermitian matrix A stored in packed form to real symmetric tridiagonal form T by an unitary similarity transformation: Q^H * A * Q = T.
- Parameters
-
[in] | Uplo | = "U": Upper triangle of A is stored.
= "L": Lower triangle of A is stored. |
[in] | N | Order 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] = a[j][i] for 0 <= i <= j <= N - 1.
Uplo = "L": ap[(i + j*(2*N - j - 1)/2] = a[j][i] for 0 <= j < = i <= N - 1.
[out] If Uplo = "U", the diagonal and first superdiagonal of Ap() are overwritten by the corresponding elements of the tridiagonal matrix T, and the elements above the first superdiagonal, with the array Tau(), represent the unitary matrix Q as a product of elementary reflectors. If Uplo = "L", the diagonal and first subdiagonal of Ap() are overwritten by the corresponding elements of the tridiagonal matrix T, and the elements below the first subdiagonal, with the array Tau(), represent the unitary matrix Q as a product of elementary reflectors. See Further Details. |
[out] | D() | Array D(LD - 1) (LD >= N)
The diagonal elements of the tridiagonal matrix T: D(i) = Tii. |
[out] | E() | Array E(LE - 1) (LE >= N - 1)
The off-diagonal elements of the tridiagonal matrix T: E(i) = T(i, i+1) if Uplo = "U", E(i) = T(i+1, i) if Uplo = "L". |
[out] | Tau() | Array Tau(LTau - 1) (LTau >= N - 1)
The scalar factors of the elementary reflectors (see Further Details). |
[out] | Info | = 0: Successful exit.
= -1: The argument Uplo had an illegal value (Uplo != "U" nor "L")
= -2: The argument N had an illegal value. (N < 0)
= -3: The argument Ap() is invalid.
= -4: The argument D() is invalid.
= -5: The argument E() is invalid.
= -6: The argument Tau() is invalid. |
- Further Details
- If Uplo = "U", the matrix Q is represented as a product of elementary reflectors
Q = H(N-1) . . . H(2) H(1).
Each H(i) has the form where tau is a complex scalar, and v is a complex vector with v(i+1〜N) = 0 and v(i) = 1. v(1〜i-1) is stored on exit in Ap(), overwriting A(1〜i-1, i+1), and tau in Tau(i-1).
If Uplo = "L", the matrix Q is represented as a product of elementary reflectors Q = H(1) H(2) . . . H(N-1).
Each H(i) has the form where tau is a complex scalar, and v is a complex vector with v(1〜i) = 0 and v(i+1) = 1; v(i+2〜N) is stored on exit in Ap(), overwriting A(i+2〜N, i), and tau in Tau(i-1).
- 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 Zhptrd, then Dsterf is applied. Sub Ex_Zhptrd_Dsterf()
Const N = 3
Dim Ap(N * (N + 1) / 2) As Complex, Info As Long
Dim D(N - 1) As Double, E(N - 2) As Double, Tau(N - 2) As Complex
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 Zhptrd("L", N, Ap(), D(), E(), Tau(), Info)
If Info <> 0 Then
Debug.Print "Error in Zhptrd: Info =", Info
Exit Sub
End If
Call Dsterf(N, D(), E(), Info)
If Info <> 0 Then
Debug.Print "Error in Dsterf: Info =", Info
Exit Sub
End If
Debug.Print "Eigenvalues =", D(0), D(1), D(2)
End Sub
- Example Results
Eigenvalues = -2.05348849668514 0.124622388617308 1.51886610806783
|