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

◆ Zgesv()

Sub Zgesv ( N As  Long,
A() As  Complex,
IPiv() As  Long,
B() As  Complex,
Info As  Long,
Optional Nrhs As  Long = 1 
)

(Simple driver) Solution to system of linear equations AX = B for a complex matrix

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

The LU decomposition with partial pivoting and row interchanges is used to factor A as
A = P * L * U
where P is a permutation matrix, L is unit lower triangular, and U is upper triangular. The factored form of A is then used to solve the system of equations A * X = B.
Parameters
[in]NNumber of linear equations, i.e., order of the matrix A. (N >= 0) (If N = 0, returns without computation)
[in,out]A()Array A(LA1 - 1, LA2 - 1) (LA1 >= N, LA2 >= N)
[in] N x N coefficient matrix A.
[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 >= N)
Pivot indices that define the permutation matrix P; row i of the matrix was interchanged with row IPiv(i-1).
[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 matrix of 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 A() is invalid.
= -3: The argument IPiv() is invalid.
= -4: The argument B() is invalid.
= -6: The argument nrhs had an illegal value. (Nrhs <= 0, or, Nrhs <> 1 and B() is 1D array)
= 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, so the solution could not be computed.
[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
( 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_Zgesv()
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 Zgesv(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