LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
cgesc2.f
Go to the documentation of this file.
1*> \brief \b CGESC2 solves a system of linear equations using the LU factorization with complete pivoting computed by sgetc2.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download CGESC2 + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cgesc2.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cgesc2.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cgesc2.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CGESC2( N, A, LDA, RHS, IPIV, JPIV, SCALE )
20*
21* .. Scalar Arguments ..
22* INTEGER LDA, N
23* REAL SCALE
24* ..
25* .. Array Arguments ..
26* INTEGER IPIV( * ), JPIV( * )
27* COMPLEX A( LDA, * ), RHS( * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> CGESC2 solves a system of linear equations
37*>
38*> A * X = scale* RHS
39*>
40*> with a general N-by-N matrix A using the LU factorization with
41*> complete pivoting computed by CGETC2.
42*>
43*> \endverbatim
44*
45* Arguments:
46* ==========
47*
48*> \param[in] N
49*> \verbatim
50*> N is INTEGER
51*> The number of columns of the matrix A.
52*> \endverbatim
53*>
54*> \param[in] A
55*> \verbatim
56*> A is COMPLEX array, dimension (LDA, N)
57*> On entry, the LU part of the factorization of the n-by-n
58*> matrix A computed by CGETC2: A = P * L * U * Q
59*> \endverbatim
60*>
61*> \param[in] LDA
62*> \verbatim
63*> LDA is INTEGER
64*> The leading dimension of the array A. LDA >= max(1, N).
65*> \endverbatim
66*>
67*> \param[in,out] RHS
68*> \verbatim
69*> RHS is COMPLEX array, dimension N.
70*> On entry, the right hand side vector b.
71*> On exit, the solution vector X.
72*> \endverbatim
73*>
74*> \param[in] IPIV
75*> \verbatim
76*> IPIV is INTEGER array, dimension (N).
77*> The pivot indices; for 1 <= i <= N, row i of the
78*> matrix has been interchanged with row IPIV(i).
79*> \endverbatim
80*>
81*> \param[in] JPIV
82*> \verbatim
83*> JPIV is INTEGER array, dimension (N).
84*> The pivot indices; for 1 <= j <= N, column j of the
85*> matrix has been interchanged with column JPIV(j).
86*> \endverbatim
87*>
88*> \param[out] SCALE
89*> \verbatim
90*> SCALE is REAL
91*> On exit, SCALE contains the scale factor. SCALE is chosen
92*> 0 <= SCALE <= 1 to prevent overflow in the solution.
93*> \endverbatim
94*
95* Authors:
96* ========
97*
98*> \author Univ. of Tennessee
99*> \author Univ. of California Berkeley
100*> \author Univ. of Colorado Denver
101*> \author NAG Ltd.
102*
103*> \ingroup gesc2
104*
105*> \par Contributors:
106* ==================
107*>
108*> Bo Kagstrom and Peter Poromaa, Department of Computing Science,
109*> Umea University, S-901 87 Umea, Sweden.
110*
111* =====================================================================
112 SUBROUTINE cgesc2( N, A, LDA, RHS, IPIV, JPIV, SCALE )
113*
114* -- LAPACK auxiliary routine --
115* -- LAPACK is a software package provided by Univ. of Tennessee, --
116* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
117*
118* .. Scalar Arguments ..
119 INTEGER LDA, N
120 REAL SCALE
121* ..
122* .. Array Arguments ..
123 INTEGER IPIV( * ), JPIV( * )
124 COMPLEX A( LDA, * ), RHS( * )
125* ..
126*
127* =====================================================================
128*
129* .. Parameters ..
130 REAL ZERO, ONE, TWO
131 parameter( zero = 0.0e+0, one = 1.0e+0, two = 2.0e+0 )
132* ..
133* .. Local Scalars ..
134 INTEGER I, J
135 REAL BIGNUM, EPS, SMLNUM
136 COMPLEX TEMP
137* ..
138* .. External Subroutines ..
139 EXTERNAL claswp, cscal
140* ..
141* .. External Functions ..
142 INTEGER ICAMAX
143 REAL SLAMCH
144 EXTERNAL icamax, slamch
145* ..
146* .. Intrinsic Functions ..
147 INTRINSIC abs, cmplx, real
148* ..
149* .. Executable Statements ..
150*
151* Set constant to control overflow
152*
153 eps = slamch( 'P' )
154 smlnum = slamch( 'S' ) / eps
155 bignum = one / smlnum
156*
157* Apply permutations IPIV to RHS
158*
159 CALL claswp( 1, rhs, lda, 1, n-1, ipiv, 1 )
160*
161* Solve for L part
162*
163 DO 20 i = 1, n - 1
164 DO 10 j = i + 1, n
165 rhs( j ) = rhs( j ) - a( j, i )*rhs( i )
166 10 CONTINUE
167 20 CONTINUE
168*
169* Solve for U part
170*
171 scale = one
172*
173* Check for scaling
174*
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 )
180 END IF
181 DO 40 i = n, 1, -1
182 temp = cmplx( one, zero ) / a( i, i )
183 rhs( i ) = rhs( i )*temp
184 DO 30 j = i + 1, n
185 rhs( i ) = rhs( i ) - rhs( j )*( a( i, j )*temp )
186 30 CONTINUE
187 40 CONTINUE
188*
189* Apply permutations JPIV to the solution (RHS)
190*
191 CALL claswp( 1, rhs, lda, 1, n-1, jpiv, -1 )
192 RETURN
193*
194* End of CGESC2
195*
196 END
subroutine cgesc2(n, a, lda, rhs, ipiv, jpiv, scale)
CGESC2 solves a system of linear equations using the LU factorization with complete pivoting computed...
Definition cgesc2.f:113
subroutine claswp(n, a, lda, k1, k2, ipiv, incx)
CLASWP performs a series of row interchanges on a general rectangular matrix.
Definition claswp.f:113
subroutine cscal(n, ca, cx, incx)
CSCAL
Definition cscal.f:78