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

◆ Zgttrf()

Sub Zgttrf ( N As  Long,
Dl() As  Complex,
D() As  Complex,
Du() As  Complex,
Du2() As  Complex,
IPiv() As  Long,
Info As  Long 
)

LU factorization of a complex tridiagonal matrix

Purpose
This routine computes an LU factorization of a complex tridiagonal matrix A using elimination with partial pivoting and row interchanges. The factorization has the form
A = L * U
where L is a product of permutation and unit lower bidiagonal matrices and U is upper triangular with nonzeros in only the main diagonal and first two super-diagonals.
Parameters
[in]NOrder of the matrix A. (N >= 0) (If N = 0, returns without computation)
[in,out]Dl()Array Dl(LDl - 1) (LDl >= N - 1)
[in] N-1 sub-diagonal elements of A.
[out] N-1 multipliers that define the matrix L from the LU factorization of A.
[in,out]D()Array D(LD - 1) (LD >= N)
[in] Diagonal elements of A.
[out] N diagonal elements of the upper triangular matrix U from the LU factorization of A.
[in,out]Du()Array Du(LDu - 1) (LDu >= N - 1)
[in] N-1 super-diagonal elements of A.
[out] N-1 elements of the first super-diagonal of U.
[out]Du2()Array Du2(LDu2 - 1) (LDu2 >= N - 2)
N-2 elements of the second super-diagonal of U.
[out]IPiv()Array IPiv(LIPiv - 1) (LIPiv >= N)
Pivot indices; for 1 <= i <= N, row i of the matrix was interchanged with row IPiv(i-1). IPiv(i-1) will always be either i or i+1; IPiv(i-1) = i indicates a row interchange was not required.
[out]Info= 0: Successful exit.
= -1: The argument N had an illegal value. (N < 0)
= -2: The argument Dl() is invalid.
= -3: The argument D() is invalid.
= -4: The argument Du() is invalid.
= -5: The argument Du2() is invalid.
= -6: The argument IPiv() is invalid.
= i > 0: The i-th diagonal element of the factor U is exactly zero. The factorization has been completed, but the factor U is exactly singular, and division by zero will occur if it is used to solve a system of equations.
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.81+0.37i -0.20-0.11i 0 )
A = ( 0.64+0.51i -0.80-0.92i -0.93-0.32i )
( 0 0.71+0.59i -0.29+0.86i )
( -0.0484+0.2644i )
B = ( -0.2644-1.0228i )
( -0.5299+1.5025i )
Sub Ex_Zgttrf()
Const N = 3
Dim Dl(N - 2) As Complex, D(N - 1) As Complex, Du(N - 2) As Complex
Dim Du2(N - 3) As Complex, IPiv(N - 1) As Long
Dim B(N - 1) As Complex, ANorm As Double, RCond As Double, Info As Long
Dl(0) = Cmplx(0.64, 0.51): Dl(1) = Cmplx(0.71, 0.59)
D(0) = Cmplx(0.81, 0.37): D(1) = Cmplx(-0.8, -0.92): D(2) = Cmplx(-0.29, 0.86)
Du(0) = Cmplx(0.2, -0.11): Du(1) = Cmplx(-0.93, -0.32)
B(0) = Cmplx(-0.0484, 0.2644): B(1) = Cmplx(-0.2644, -1.0228): B(2) = Cmplx(-0.5299, 1.5025)
ANorm = Zlangt("1", N, Dl(), D(), Du())
Call Zgttrf(N, Dl(), D(), Du(), Du2(), IPiv(), Info)
If Info = 0 Then Call Zgttrs("N", N, Dl(), D(), Du(), Du2(), IPiv(), B(), Info)
If Info = 0 Then Call Zgtcon("1", N, Dl(), D(), Du(), Du2(), 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
Example Results
X = -0.15 0.19 0.2 0.94 0.79 -0.13
RCond = 0.187722560135325
Info = 0