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

◆ Zgetrf()

Sub Zgetrf ( M As  Long,
N As  Long,
A() As  Complex,
IPiv() As  Long,
Info As  Long 
)

LU factorization of a complex matrix

Purpose
This routine computes an LU factorization of a complex m x n matrix A using partial pivoting with row interchanges. The factorization has the form
A = P * L * U
where P is a permutation matrix, L is lower triangular with unit diagonal elements (lower trapezoidal if m > n), and U is upper triangular (upper trapezoidal if m < n).
This is the right-looking Level 3 BLAS version of the algorithm.
Parameters
[in]MNumber of rows of the matrix A. (M >= 0) (If M = 0, returns without computation)
[in]NNumber of columns of the matrix A. (N >= 0) (If N = 0, returns without computation)
[in,out]A()Array A(LA1 - 1, LA2 - 1) (LA1 >= M, LA2 >= N)
[in] M x N matrix to be factored.
[out] Factors L and U from the factorization A = P*L*U. The unit diagonal elements of L are not stored.
[out]IPiv()Array IPiv(LIPiv - 1) (LIPiv >= min(M, N))
Pivot indices; for 1 <= i <= min(M, N), row i of the matrix was interchanged with row IPiv(i-1).
[out]Info= 0: Successful exit.
= -1: The argument M had an illegal value. (M < 0)
= -2: The argument M had an illegal value. (N < 0)
= -3: The argument A() is invalid.
= -4: 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.2-0.11i -0.93-0.32i 0.81+0.37i )
A = ( -0.8-0.92i -0.29+0.86i 0.64+0.51i )
( 0.71+0.59i -0.15+0.19i 0.2+0.94i )
( -0.5853-0.9457i )
B = ( -2.1697-1.0006i )
( 0.0116-0.5094i )
Sub Ex_Zgetrf()
Const N = 3
Dim A(N - 1, N - 1) As Complex, B(N - 1) As Complex, IPiv(N - 1) As Long
Dim ANorm As Double, RCond As Double, Info As Long
A(0, 0) = Cmplx(0.2, -0.11): A(0, 1) = Cmplx(-0.93, -0.32): A(0, 2) = Cmplx(0.81, 0.37)
A(1, 0) = Cmplx(-0.8, -0.92): A(1, 1) = Cmplx(-0.29, 0.86): A(1, 2) = Cmplx(0.64, 0.51)
A(2, 0) = Cmplx(0.71, 0.59): A(2, 1) = Cmplx(-0.15, 0.19): A(2, 2) = Cmplx(0.2, 0.94)
B(0) = Cmplx(-0.5853, -0.9457): B(1) = Cmplx(-2.1697, -1.0006): B(2) = Cmplx(0.0116, -0.5094)
ANorm = Zlange("1", N, N, A())
Call Zgetrf(N, N, A(), IPiv(), Info)
If Info = 0 Then Call Zgetrs("N", N, A(), IPiv(), B(), Info)
If Info = 0 Then Call Zgecon("1", N, A(), ANorm, RCond, Info)
Debug.Print "X =", 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.79 -0.13 0.13 0.75 -0.91 0.3
RCond = 0.250214147937285
Info = 0