LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dgesc2.f
Go to the documentation of this file.
1*> \brief \b DGESC2 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 DGESC2 + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dgesc2.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dgesc2.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgesc2.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DGESC2( N, A, LDA, RHS, IPIV, JPIV, SCALE )
20*
21* .. Scalar Arguments ..
22* INTEGER LDA, N
23* DOUBLE PRECISION SCALE
24* ..
25* .. Array Arguments ..
26* INTEGER IPIV( * ), JPIV( * )
27* DOUBLE PRECISION A( LDA, * ), RHS( * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> DGESC2 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 DGETC2.
42*> \endverbatim
43*
44* Arguments:
45* ==========
46*
47*> \param[in] N
48*> \verbatim
49*> N is INTEGER
50*> The order of the matrix A.
51*> \endverbatim
52*>
53*> \param[in] A
54*> \verbatim
55*> A is DOUBLE PRECISION array, dimension (LDA,N)
56*> On entry, the LU part of the factorization of the n-by-n
57*> matrix A computed by DGETC2: A = P * L * U * Q
58*> \endverbatim
59*>
60*> \param[in] LDA
61*> \verbatim
62*> LDA is INTEGER
63*> The leading dimension of the array A. LDA >= max(1, N).
64*> \endverbatim
65*>
66*> \param[in,out] RHS
67*> \verbatim
68*> RHS is DOUBLE PRECISION array, dimension (N).
69*> On entry, the right hand side vector b.
70*> On exit, the solution vector X.
71*> \endverbatim
72*>
73*> \param[in] IPIV
74*> \verbatim
75*> IPIV is INTEGER array, dimension (N).
76*> The pivot indices; for 1 <= i <= N, row i of the
77*> matrix has been interchanged with row IPIV(i).
78*> \endverbatim
79*>
80*> \param[in] JPIV
81*> \verbatim
82*> JPIV is INTEGER array, dimension (N).
83*> The pivot indices; for 1 <= j <= N, column j of the
84*> matrix has been interchanged with column JPIV(j).
85*> \endverbatim
86*>
87*> \param[out] SCALE
88*> \verbatim
89*> SCALE is DOUBLE PRECISION
90*> On exit, SCALE contains the scale factor. SCALE is chosen
91*> 0 <= SCALE <= 1 to prevent overflow in the solution.
92*> \endverbatim
93*
94* Authors:
95* ========
96*
97*> \author Univ. of Tennessee
98*> \author Univ. of California Berkeley
99*> \author Univ. of Colorado Denver
100*> \author NAG Ltd.
101*
102*> \ingroup gesc2
103*
104*> \par Contributors:
105* ==================
106*>
107*> Bo Kagstrom and Peter Poromaa, Department of Computing Science,
108*> Umea University, S-901 87 Umea, Sweden.
109*
110* =====================================================================
111 SUBROUTINE dgesc2( N, A, LDA, RHS, IPIV, JPIV, SCALE )
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 DOUBLE PRECISION SCALE
120* ..
121* .. Array Arguments ..
122 INTEGER IPIV( * ), JPIV( * )
123 DOUBLE PRECISION A( LDA, * ), RHS( * )
124* ..
125*
126* =====================================================================
127*
128* .. Parameters ..
129 DOUBLE PRECISION ONE, TWO
130 parameter( one = 1.0d+0, two = 2.0d+0 )
131* ..
132* .. Local Scalars ..
133 INTEGER I, J
134 DOUBLE PRECISION BIGNUM, EPS, SMLNUM, TEMP
135* ..
136* .. External Subroutines ..
137 EXTERNAL dlaswp, dscal
138* ..
139* .. External Functions ..
140 INTEGER IDAMAX
141 DOUBLE PRECISION DLAMCH
142 EXTERNAL idamax, dlamch
143* ..
144* .. Intrinsic Functions ..
145 INTRINSIC abs
146* ..
147* .. Executable Statements ..
148*
149* Set constant to control overflow
150*
151 eps = dlamch( 'P' )
152 smlnum = dlamch( 'S' ) / eps
153 bignum = one / smlnum
154*
155* Apply permutations IPIV to RHS
156*
157 CALL dlaswp( 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 = idamax( 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 dscal( 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 dlaswp( 1, rhs, lda, 1, n-1, jpiv, -1 )
191 RETURN
192*
193* End of DGESC2
194*
195 END
subroutine dgesc2(n, a, lda, rhs, ipiv, jpiv, scale)
DGESC2 solves a system of linear equations using the LU factorization with complete pivoting computed...
Definition dgesc2.f:112
subroutine dlaswp(n, a, lda, k1, k2, ipiv, incx)
DLASWP performs a series of row interchanges on a general rectangular matrix.
Definition dlaswp.f:113
subroutine dscal(n, da, dx, incx)
DSCAL
Definition dscal.f:79