LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
sgetc2.f
Go to the documentation of this file.
1*> \brief \b SGETC2 computes the LU factorization with complete pivoting of the general n-by-n matrix.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download SGETC2 + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sgetc2.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sgetc2.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sgetc2.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE SGETC2( N, A, LDA, IPIV, JPIV, INFO )
20*
21* .. Scalar Arguments ..
22* INTEGER INFO, LDA, N
23* ..
24* .. Array Arguments ..
25* INTEGER IPIV( * ), JPIV( * )
26* REAL A( LDA, * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> SGETC2 computes an LU factorization with complete pivoting of the
36*> n-by-n matrix A. The factorization has the form A = P * L * U * Q,
37*> where P and Q are permutation matrices, L is lower triangular with
38*> unit diagonal elements and U is upper triangular.
39*>
40*> This is the Level 2 BLAS algorithm.
41*> \endverbatim
42*
43* Arguments:
44* ==========
45*
46*> \param[in] N
47*> \verbatim
48*> N is INTEGER
49*> The order of the matrix A. N >= 0.
50*> \endverbatim
51*>
52*> \param[in,out] A
53*> \verbatim
54*> A is REAL array, dimension (LDA, N)
55*> On entry, the n-by-n matrix A to be factored.
56*> On exit, the factors L and U from the factorization
57*> A = P*L*U*Q; the unit diagonal elements of L are not stored.
58*> If U(k, k) appears to be less than SMIN, U(k, k) is given the
59*> value of SMIN, i.e., giving a nonsingular perturbed system.
60*> \endverbatim
61*>
62*> \param[in] LDA
63*> \verbatim
64*> LDA is INTEGER
65*> The leading dimension of the array A. LDA >= max(1,N).
66*> \endverbatim
67*>
68*> \param[out] IPIV
69*> \verbatim
70*> IPIV is INTEGER array, dimension(N).
71*> The pivot indices; for 1 <= i <= N, row i of the
72*> matrix has been interchanged with row IPIV(i).
73*> \endverbatim
74*>
75*> \param[out] JPIV
76*> \verbatim
77*> JPIV is INTEGER array, dimension(N).
78*> The pivot indices; for 1 <= j <= N, column j of the
79*> matrix has been interchanged with column JPIV(j).
80*> \endverbatim
81*>
82*> \param[out] INFO
83*> \verbatim
84*> INFO is INTEGER
85*> = 0: successful exit
86*> > 0: if INFO = k, U(k, k) is likely to produce overflow if
87*> we try to solve for x in Ax = b. So U is perturbed to
88*> avoid the overflow.
89*> \endverbatim
90*
91* Authors:
92* ========
93*
94*> \author Univ. of Tennessee
95*> \author Univ. of California Berkeley
96*> \author Univ. of Colorado Denver
97*> \author NAG Ltd.
98*
99*> \ingroup getc2
100*
101*> \par Contributors:
102* ==================
103*>
104*> Bo Kagstrom and Peter Poromaa, Department of Computing Science,
105*> Umea University, S-901 87 Umea, Sweden.
106*
107* =====================================================================
108 SUBROUTINE sgetc2( N, A, LDA, IPIV, JPIV, INFO )
109*
110* -- LAPACK auxiliary routine --
111* -- LAPACK is a software package provided by Univ. of Tennessee, --
112* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
113*
114* .. Scalar Arguments ..
115 INTEGER INFO, LDA, N
116* ..
117* .. Array Arguments ..
118 INTEGER IPIV( * ), JPIV( * )
119 REAL A( LDA, * )
120* ..
121*
122* =====================================================================
123*
124* .. Parameters ..
125 REAL ZERO, ONE
126 parameter( zero = 0.0e+0, one = 1.0e+0 )
127* ..
128* .. Local Scalars ..
129 INTEGER I, IP, IPV, J, JP, JPV
130 REAL BIGNUM, EPS, SMIN, SMLNUM, XMAX
131* ..
132* .. External Subroutines ..
133 EXTERNAL sger, sswap
134* ..
135* .. External Functions ..
136 REAL SLAMCH
137 EXTERNAL slamch
138* ..
139* .. Intrinsic Functions ..
140 INTRINSIC abs, max
141* ..
142* .. Executable Statements ..
143*
144 info = 0
145*
146* Quick return if possible
147*
148 IF( n.EQ.0 )
149 $ RETURN
150*
151* Set constants to control overflow
152*
153 eps = slamch( 'P' )
154 smlnum = slamch( 'S' ) / eps
155 bignum = one / smlnum
156*
157* Handle the case N=1 by itself
158*
159 IF( n.EQ.1 ) THEN
160 ipiv( 1 ) = 1
161 jpiv( 1 ) = 1
162 IF( abs( a( 1, 1 ) ).LT.smlnum ) THEN
163 info = 1
164 a( 1, 1 ) = smlnum
165 END IF
166 RETURN
167 END IF
168*
169* Factorize A using complete pivoting.
170* Set pivots less than SMIN to SMIN.
171*
172 DO 40 i = 1, n - 1
173*
174* Find max element in matrix A
175*
176 xmax = zero
177 DO 20 jp = i, n
178 DO 10 ip = i, n
179 IF( abs( a( ip, jp ) ).GE.xmax ) THEN
180 xmax = abs( a( ip, jp ) )
181 ipv = ip
182 jpv = jp
183 END IF
184 10 CONTINUE
185 20 CONTINUE
186 IF( i.EQ.1 )
187 $ smin = max( eps*xmax, smlnum )
188*
189* Swap rows
190*
191 IF( ipv.NE.i )
192 $ CALL sswap( n, a( ipv, 1 ), lda, a( i, 1 ), lda )
193 ipiv( i ) = ipv
194*
195* Swap columns
196*
197 IF( jpv.NE.i )
198 $ CALL sswap( n, a( 1, jpv ), 1, a( 1, i ), 1 )
199 jpiv( i ) = jpv
200*
201* Check for singularity
202*
203 IF( abs( a( i, i ) ).LT.smin ) THEN
204 info = i
205 a( i, i ) = smin
206 END IF
207 DO 30 j = i + 1, n
208 a( j, i ) = a( j, i ) / a( i, i )
209 30 CONTINUE
210 CALL sger( n-i, n-i, -one, a( i+1, i ), 1, a( i, i+1 ), lda,
211 $ a( i+1, i+1 ), lda )
212 40 CONTINUE
213*
214 IF( abs( a( n, n ) ).LT.smin ) THEN
215 info = n
216 a( n, n ) = smin
217 END IF
218*
219* Set last pivots to N
220*
221 ipiv( n ) = n
222 jpiv( n ) = n
223*
224 RETURN
225*
226* End of SGETC2
227*
228 END
subroutine sger(m, n, alpha, x, incx, y, incy, a, lda)
SGER
Definition sger.f:130
subroutine sgetc2(n, a, lda, ipiv, jpiv, info)
SGETC2 computes the LU factorization with complete pivoting of the general n-by-n matrix.
Definition sgetc2.f:109
subroutine sswap(n, sx, incx, sy, incy)
SSWAP
Definition sswap.f:82