XLPack 7.0
XLPack Numerical Library (Excel VBA) Reference Manual
Loading...
Searching...
No Matches

◆ Zhptrf()

Sub Zhptrf ( Uplo As  String,
N As  Long,
Ap() As  Complex,
IPiv() As  Long,
Info As  Long 
)

UDUH or LDLH factorization of a Hermitian matrix in packed form

Purpose
This routine computes the factorization of a Hermitian matrix A stored in packed form using the Bunch-Kaufman diagonal pivoting method:
A = U*D*U^H or A = L*D*L^H
where U (or L) is a product of permutation and unit upper (lower) triangular matrices, and D is Hermitian and block diagonal with 1 x 1 and 2 x 2 diagonal blocks.
Parameters
[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] N x N Hermitian matrix A in packed form. The upper or lower part is to be stored in accordance with Uplo.
[out] The block diagonal matrix D and the multipliers used to obtain the factor U or L, stored as a packed triangular matrix overwriting A (see below for further details).
[out]IPiv()Array IPiv(LIPiv - 1) (LIPiv >= N)
Details of the interchanges and the block structure of D. If IPiv(k-1) > 0, then rows and columns k and IPiv(k-1) were interchanged, and k-th diagonal of D is a 1 x 1 diagonal block.
  If Uplo = "U" and IPiv(k-1) = IPiv(k-2) < 0, then rows and columns k-1 and -IPiv(k-1) were interchanged and (k-1)-th diagonal of D is a 2 x 2 diagonal block.
  If Uplo = "L" and IPiv(k-1) = IPiv(k) < 0, then rows and columns k+1 and -IPiv(k-1) were interchanged and k-th diagonal of D is a 2 x 2 diagonal block.
[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 IPiv() is invalid.
= i > 0: The i-th diagonal element of D is exactly zero. The factorization has been completed, but the block diagonal matrix D is exactly singular, and division by zero will occur if it is used to solve a system of equations.
Further Details
If Uplo = "U", then A = U*D*U^H, where
U = P(n)*U(n)* ... *P(k)U(k)* ...,
i.e., U is a product of terms P(k)*U(k), where k decreases from n to 1 in steps of 1 or 2, and D is a block diagonal matrix with 1 x 1 and 2 x 2 diagonal blocks D(k). P(k) is a permutation matrix as defined by IPiv(k-1), and U(k) is a unit upper triangular matrix, such that if the diagonal block D(k) is of order s (s = 1 or 2), then
( I v 0 ) k-s
U(k) = ( 0 I 0 ) s
( 0 0 I ) n-k
k-s s n-k
If s = 1, D(k) overwrites A(k-1, k-1), and v overwrites A(0 to k-2, k-1).
If s = 2, the upper triangle of D(k) overwrites A(k-2, k-2), A(k-2, k-1), and A(k-1, k-1), and v overwrites A(0 to k-3, k-2 to k-1).

If Uplo = "L", then A = L*D*L^H, where
L = P(1)*L(1)* ... *P(k)*L(k)* ...,
i.e., L is a product of terms P(k)*L(k), where k increases from 1 to n in steps of 1 or 2, and D is a block diagonal matrix with 1 x 1 and 2 x 2 diagonal blocks D(k). P(k) is a permutation matrix as defined by IPiv(k-1), and L(k) is a unit lower triangular matrix, such that if the diagonal block D(k) is of order s (s = 1 or 2), then
( I 0 0 ) k-1
L(k) = ( 0 I 0 ) s
( 0 v I ) n-k-s+1
k-1 s n-k-s+1
If s = 1, D(k) overwrites A(k-1, k-1), and v overwrites A(k to n-1, k-1).
If s = 2, the lower triangle of D(k) overwrites A(k-1, k-1), A(k-1, k), and A(k, k), and v overwrites A(k+1 to n-1, k-1 to k).

Note - A(i,j) shows the element of Ap() corresponding to that in row i and column j of A.
Reference
LAPACK
Example Program
Solve the system of linear equations Ax = B and estimate the reciprocal of the condition number (RCond) of 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 )
( -0.1220+0.1844i )
B = ( 0.0034-0.4346i )
( 0.5339-0.1571i )
Sub Ex_Zhptrf()
Const N As Long = 3
Dim Ap(N * (N + 1) / 2) As Complex, B(N - 1) As Complex, IPiv(N - 1) As Long
Dim ANorm As Double, RCond As Double, 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)
B(0) = Cmplx(-0.122, 0.1844): B(1) = Cmplx(0.0034, -0.4346): B(2) = Cmplx(0.5339, -0.1571)
ANorm = Zlanhp("1", "L", N, Ap())
Call Zhptrf("L", N, Ap(), IPiv(), Info)
If Info = 0 Then Call Zhptrs("L", N, Ap(), IPiv(), B(), Info)
If Info = 0 Then Call Zhpcon("L", N, Ap(), IPiv(), ANorm, RCond, Info)
Debug.Print "X =",
Debug.Print Creal(B(0)), Cimag(B(0)), Creal(B(1)), Cimag(B(1)), Creal(B(2)), Cimag(B(2))
Debug.Print "RCond =", RCond
Debug.Print "Info =", Info
End Sub
Function Cmplx(R As Double, Optional I As Double=0) As Complex
Building complex number
Function Cimag(A As Complex) As Double
Imaginary part of complex number
Function Creal(A As Complex) As Double
Real part of complex number
Function Zlanhp(Norm As String, Uplo As String, N As Long, Ap() As Complex, Optional Info As Long) As Double
One norm, Frobenius norm, infinity norm, or largest absolute value of any element of a Hermitian matr...
Sub Zhpcon(Uplo As String, N As Long, Ap() As Complex, IPiv() As Long, ANorm As Double, RCond As Double, Info As Long)
Condition number of a Hermitian matrix in packed form
Sub Zhptrf(Uplo As String, N As Long, Ap() As Complex, IPiv() As Long, Info As Long)
UDUH or LDLH factorization of a Hermitian matrix in packed form
Sub Zhptrs(Uplo As String, N As Long, Ap() As Complex, IPiv() As Long, B() As Complex, Info As Long, Optional Nrhs As Long=1)
Solution to factorized system of linear equations AX = B for a Hermitian matrix in packed form
Example Results
X = 0.86 0.64 0.51 0.71 0.590000000000001 -0.15
RCond = 4.46158691608911E-02
Info = 0