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

◆ sgesc2()

subroutine sgesc2 ( integer n,
real, dimension( lda, * ) a,
integer lda,
real, dimension( * ) rhs,
integer, dimension( * ) ipiv,
integer, dimension( * ) jpiv,
real scale )

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

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

Purpose:
!>
!> SGESC2 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 SGETC2.
!> 
Parameters
[in]N
!>          N is INTEGER
!>          The order of the matrix A.
!> 
[in]A
!>          A is REAL array, dimension (LDA,N)
!>          On entry, the  LU part of the factorization of the n-by-n
!>          matrix A computed by SGETC2:  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 REAL 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 REAL
!>           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 111 of file sgesc2.f.

112*
113* -- LAPACK auxiliary routine --
114* -- LAPACK is a software package provided by Univ. of Tennessee, --
115* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
116*
117* .. Scalar Arguments ..
118 INTEGER LDA, N
119 REAL SCALE
120* ..
121* .. Array Arguments ..
122 INTEGER IPIV( * ), JPIV( * )
123 REAL A( LDA, * ), RHS( * )
124* ..
125*
126* =====================================================================
127*
128* .. Parameters ..
129 REAL ONE, TWO
130 parameter( one = 1.0e+0, two = 2.0e+0 )
131* ..
132* .. Local Scalars ..
133 INTEGER I, J
134 REAL BIGNUM, EPS, SMLNUM, TEMP
135* ..
136* .. External Subroutines ..
137 EXTERNAL slaswp, sscal
138* ..
139* .. External Functions ..
140 INTEGER ISAMAX
141 REAL SLAMCH
142 EXTERNAL isamax, slamch
143* ..
144* .. Intrinsic Functions ..
145 INTRINSIC abs
146* ..
147* .. Executable Statements ..
148*
149* Set constant to control overflow
150*
151 eps = slamch( 'P' )
152 smlnum = slamch( 'S' ) / eps
153 bignum = one / smlnum
154*
155* Apply permutations IPIV to RHS
156*
157 CALL slaswp( 1, rhs, lda, 1, n-1, ipiv, 1 )
158*
159* Solve for L part
160*
161 DO 20 i = 1, n - 1
162 DO 10 j = i + 1, n
163 rhs( j ) = rhs( j ) - a( j, i )*rhs( i )
164 10 CONTINUE
165 20 CONTINUE
166*
167* Solve for U part
168*
169 scale = one
170*
171* Check for scaling
172*
173 i = isamax( n, rhs, 1 )
174 IF( two*smlnum*abs( rhs( i ) ).GT.abs( a( n, n ) ) ) THEN
175 temp = ( one / two ) / abs( rhs( i ) )
176 CALL sscal( n, temp, rhs( 1 ), 1 )
177 scale = scale*temp
178 END IF
179*
180 DO 40 i = n, 1, -1
181 temp = one / a( i, i )
182 rhs( i ) = rhs( i )*temp
183 DO 30 j = i + 1, n
184 rhs( i ) = rhs( i ) - rhs( j )*( a( i, j )*temp )
185 30 CONTINUE
186 40 CONTINUE
187*
188* Apply permutations JPIV to the solution (RHS)
189*
190 CALL slaswp( 1, rhs, lda, 1, n-1, jpiv, -1 )
191 RETURN
192*
193* End of SGESC2
194*
integer function isamax(n, sx, incx)
ISAMAX
Definition isamax.f:71
real function slamch(cmach)
SLAMCH
Definition slamch.f:68
subroutine slaswp(n, a, lda, k1, k2, ipiv, incx)
SLASWP performs a series of row interchanges on a general rectangular matrix.
Definition slaswp.f:113
subroutine sscal(n, sa, sx, incx)
SSCAL
Definition sscal.f:79
Here is the call graph for this function:
Here is the caller graph for this function: