LAPACK 3.11.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ zgesc2()

subroutine zgesc2 ( integer  N,
complex*16, dimension( lda, * )  A,
integer  LDA,
complex*16, dimension( * )  RHS,
integer, dimension( * )  IPIV,
integer, dimension( * )  JPIV,
double precision  SCALE 
)

ZGESC2 solves a system of linear equations using the LU factorization with complete pivoting computed by sgetc2.

Download ZGESC2 + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 ZGESC2 solves a system of linear equations

           A * X = scale* RHS

 with a general N-by-N matrix A using the LU factorization with
 complete pivoting computed by ZGETC2.
Parameters
[in]N
          N is INTEGER
          The number of columns of the matrix A.
[in]A
          A is COMPLEX*16 array, dimension (LDA, N)
          On entry, the  LU part of the factorization of the n-by-n
          matrix A computed by ZGETC2:  A = P * L * U * Q
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1, N).
[in,out]RHS
          RHS is COMPLEX*16 array, dimension N.
          On entry, the right hand side vector b.
          On exit, the solution vector X.
[in]IPIV
          IPIV is INTEGER array, dimension (N).
          The pivot indices; for 1 <= i <= N, row i of the
          matrix has been interchanged with row IPIV(i).
[in]JPIV
          JPIV is INTEGER array, dimension (N).
          The pivot indices; for 1 <= j <= N, column j of the
          matrix has been interchanged with column JPIV(j).
[out]SCALE
          SCALE is DOUBLE PRECISION
           On exit, SCALE contains the scale factor. SCALE is chosen
           0 <= SCALE <= 1 to prevent overflow in the solution.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Contributors:
Bo Kagstrom and Peter Poromaa, Department of Computing Science, Umea University, S-901 87 Umea, Sweden.

Definition at line 114 of file zgesc2.f.

115*
116* -- LAPACK auxiliary routine --
117* -- LAPACK is a software package provided by Univ. of Tennessee, --
118* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
119*
120* .. Scalar Arguments ..
121 INTEGER LDA, N
122 DOUBLE PRECISION SCALE
123* ..
124* .. Array Arguments ..
125 INTEGER IPIV( * ), JPIV( * )
126 COMPLEX*16 A( LDA, * ), RHS( * )
127* ..
128*
129* =====================================================================
130*
131* .. Parameters ..
132 DOUBLE PRECISION ZERO, ONE, TWO
133 parameter( zero = 0.0d+0, one = 1.0d+0, two = 2.0d+0 )
134* ..
135* .. Local Scalars ..
136 INTEGER I, J
137 DOUBLE PRECISION BIGNUM, EPS, SMLNUM
138 COMPLEX*16 TEMP
139* ..
140* .. External Subroutines ..
141 EXTERNAL zlaswp, zscal, dlabad
142* ..
143* .. External Functions ..
144 INTEGER IZAMAX
145 DOUBLE PRECISION DLAMCH
146 EXTERNAL izamax, dlamch
147* ..
148* .. Intrinsic Functions ..
149 INTRINSIC abs, dble, dcmplx
150* ..
151* .. Executable Statements ..
152*
153* Set constant to control overflow
154*
155 eps = dlamch( 'P' )
156 smlnum = dlamch( 'S' ) / eps
157 bignum = one / smlnum
158 CALL dlabad( smlnum, bignum )
159*
160* Apply permutations IPIV to RHS
161*
162 CALL zlaswp( 1, rhs, lda, 1, n-1, ipiv, 1 )
163*
164* Solve for L part
165*
166 DO 20 i = 1, n - 1
167 DO 10 j = i + 1, n
168 rhs( j ) = rhs( j ) - a( j, i )*rhs( i )
169 10 CONTINUE
170 20 CONTINUE
171*
172* Solve for U part
173*
174 scale = one
175*
176* Check for scaling
177*
178 i = izamax( n, rhs, 1 )
179 IF( two*smlnum*abs( rhs( i ) ).GT.abs( a( n, n ) ) ) THEN
180 temp = dcmplx( one / two, zero ) / abs( rhs( i ) )
181 CALL zscal( n, temp, rhs( 1 ), 1 )
182 scale = scale*dble( temp )
183 END IF
184 DO 40 i = n, 1, -1
185 temp = dcmplx( one, zero ) / a( i, i )
186 rhs( i ) = rhs( i )*temp
187 DO 30 j = i + 1, n
188 rhs( i ) = rhs( i ) - rhs( j )*( a( i, j )*temp )
189 30 CONTINUE
190 40 CONTINUE
191*
192* Apply permutations JPIV to the solution (RHS)
193*
194 CALL zlaswp( 1, rhs, lda, 1, n-1, jpiv, -1 )
195 RETURN
196*
197* End of ZGESC2
198*
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:69
subroutine dlabad(SMALL, LARGE)
DLABAD
Definition: dlabad.f:74
integer function izamax(N, ZX, INCX)
IZAMAX
Definition: izamax.f:71
subroutine zscal(N, ZA, ZX, INCX)
ZSCAL
Definition: zscal.f:78
subroutine zlaswp(N, A, LDA, K1, K2, IPIV, INCX)
ZLASWP performs a series of row interchanges on a general rectangular matrix.
Definition: zlaswp.f:115
Here is the call graph for this function:
Here is the caller graph for this function: