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

◆ Zptsv()

Sub Zptsv ( N As  Long,
D() As  Double,
E() As  Complex,
B() As  Complex,
Info As  Long,
Optional Nrhs As  Long = 1 
)

(Simple driver) Solution to system of linear equations AX = B for a Hermitian positive definite tridiagonal matrix

Purpose
This routine computes the solution to a complex system of linear equations
A * X = B,
where A is an N x N Hermitian positive definite tridiagonal matrix, and X and B are N x Nrhs matrices.

A is factored as A = L*D*L^H, and the factored form of A is then used to solve the system of equations.
Parameters
[in]NOrder of the matrix A. (N >= 0) (If N = 0, returns without computation)
[in,out]D()Array D(LD - 1) (LD >= N)
[in] N diagonal elements of the Hermitian positive definite tridiagonal matrix A.
[out] N diagonal elements of the diagonal matrix D from the factorization A = L*D*L^T.
[in,out]E()Array E(LE - 1) (LE >= N - 1)
[in] N-1 sub-diagonal elements of the Hermintian positive definite tridiagonal matrix A.
[out] N-1 sub-diagonal elements of the unit bidiagonal factor L from the L*D*L^T factorization of A. E can also be regarded as the super-diagonal of the unit bidiagonal factor U from the U^T*D*U factorization of A.
[in,out]B()Array B(LB1 - 1, LB2 - 1) (LB1 >= max(1, N), LB2 >= Nrhs) (2D array) or B(LB - 1) (LB >= max(1, N), Nrhs = 1) (1D array)
[in] N x Nrhs right hand side matrix B.
[out] If Info = 0, the N x Nrhs solution matrix X.
[out]Info= 0: Successful exit.
= -1: The argument N had an illegal value. (N < 0)
= -2: The argument D() is invalid.
= -3: The argument E() is invalid.
= -4: The argument B() is invalid.
= -6: The argument Nrhs had an illegal value. (Nrhs < 0)
= i > 0: The leading minor of order i is not positive definite, and the solution has not been computed. The factorization has not been completed unless i = N.
[in]Nrhs(Optional)
Number of right hand sides, i.e., number of columns of the matrix B. (Nrhs >= 0) (If Nrhs = 0, returns without computation) (default = 1)
Reference
LAPACK
Example Program
Solve the system of linear equations Ax = B and estimate the reciprocal of the condition number (RCond) of A, where
( 2.88 0.29-0.44i 0 )
A = ( 0.29+0.44i 0.62 -0.01-0.02i )
( 0 -0.01+0.02i 0.46 )
( 1.6236-0.7300i )
B = ( 0.1581+0.1537i )
( 0.1132-0.2290i )
Sub Ex_Zptsv()
Const N As Long = 3
Dim D(N - 1) As Double, E(N - 2) As Complex, B(N - 1) As Complex
Dim ANorm As Double, RCond As Double, Info As Long
D(0) = 2.88: D(1) = 0.62: D(2) = 0.46
E(0) = Cmplx(0.29, 0.44): E(1) = Cmplx(-0.01, 0.02)
B(0) = Cmplx(1.6236, -0.73): B(1) = Cmplx(0.1581, 0.1537): B(2) = Cmplx(0.1132, -0.229)
ANorm = Zlanht("1", N, D(), E())
Call Zptsv(N, D(), E(), B(), Info)
If Info = 0 Then Call Zptcon(N, D(), E(), 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
Example Results
X = 0.59 -0.28 -0.2 -0.04 0.24 -0.49
RCond = 0.124521368143895
Info = 0