114 SUBROUTINE zgesc2( N, A, LDA, RHS, IPIV, JPIV, SCALE )
122 DOUBLE PRECISION SCALE
125 INTEGER IPIV( * ), JPIV( * )
126 COMPLEX*16 A( LDA, * ), RHS( * )
132 DOUBLE PRECISION ZERO, ONE, TWO
133 parameter( zero = 0.0d+0, one = 1.0d+0, two = 2.0d+0 )
137 DOUBLE PRECISION BIGNUM, EPS, SMLNUM
145 DOUBLE PRECISION DLAMCH
146 EXTERNAL izamax, dlamch
149 INTRINSIC abs, dble, dcmplx
156 smlnum = dlamch(
'S' ) / eps
157 bignum = one / smlnum
161 CALL zlaswp( 1, rhs, lda, 1, n-1, ipiv, 1 )
167 rhs( j ) = rhs( j ) - a( j, i )*rhs( i )
177 i = izamax( n, rhs, 1 )
178 IF( two*smlnum*abs( rhs( i ) ).GT.abs( a( n, n ) ) )
THEN
179 temp = dcmplx( one / two, zero ) / abs( rhs( i ) )
180 CALL zscal( n, temp, rhs( 1 ), 1 )
181 scale = scale*dble( temp )
184 temp = dcmplx( one, zero ) / a( i, i )
185 rhs( i ) = rhs( i )*temp
187 rhs( i ) = rhs( i ) - rhs( j )*( a( i, j )*temp )
193 CALL zlaswp( 1, rhs, lda, 1, n-1, jpiv, -1 )
subroutine zgesc2(n, a, lda, rhs, ipiv, jpiv, scale)
ZGESC2 solves a system of linear equations using the LU factorization with complete pivoting computed...
subroutine zlaswp(n, a, lda, k1, k2, ipiv, incx)
ZLASWP performs a series of row interchanges on a general rectangular matrix.
subroutine zscal(n, za, zx, incx)
ZSCAL