112      SUBROUTINE cgesc2( N, A, LDA, RHS, IPIV, JPIV, SCALE )
 
  123      INTEGER            IPIV( * ), JPIV( * )
 
  124      COMPLEX            A( LDA, * ), RHS( * )
 
  131      parameter( zero = 0.0e+0, one = 1.0e+0, two = 2.0e+0 )
 
  135      REAL               BIGNUM, EPS, SMLNUM
 
  144      EXTERNAL           icamax, slamch
 
  147      INTRINSIC          abs, cmplx, real
 
  154      smlnum = slamch( 
'S' ) / eps
 
  155      bignum = one / smlnum
 
  159      CALL claswp( 1, rhs, lda, 1, n-1, ipiv, 1 )
 
  165            rhs( j ) = rhs( j ) - a( j, i )*rhs( i )
 
  175      i = icamax( n, rhs, 1 )
 
  176      IF( two*smlnum*abs( rhs( i ) ).GT.abs( a( n, n ) ) ) 
THEN 
  177         temp = cmplx( one / two, zero ) / abs( rhs( i ) )
 
  178         CALL cscal( n, temp, rhs( 1 ), 1 )
 
  179         scale = scale*real( temp )
 
  182         temp = cmplx( one, zero ) / a( i, i )
 
  183         rhs( i ) = rhs( i )*temp
 
  185            rhs( i ) = rhs( i ) - rhs( j )*( a( i, j )*temp )
 
  191      CALL claswp( 1, rhs, lda, 1, n-1, jpiv, -1 )
 
 
subroutine cgesc2(n, a, lda, rhs, ipiv, jpiv, scale)
CGESC2 solves a system of linear equations using the LU factorization with complete pivoting computed...
subroutine claswp(n, a, lda, k1, k2, ipiv, incx)
CLASWP performs a series of row interchanges on a general rectangular matrix.