LAPACK 3.11.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
sgetrf.f
Go to the documentation of this file.
1C> \brief \b SGETRF VARIANT: Crout Level 3 BLAS version of the algorithm.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8* Definition:
9* ===========
10*
11* SUBROUTINE SGETRF ( M, N, A, LDA, IPIV, INFO)
12*
13* .. Scalar Arguments ..
14* INTEGER INFO, LDA, M, N
15* ..
16* .. Array Arguments ..
17* INTEGER IPIV( * )
18* REAL A( LDA, * )
19* ..
20*
21* Purpose
22* =======
23*
24C>\details \b Purpose:
25C>\verbatim
26C>
27C> SGETRF computes an LU factorization of a general M-by-N matrix A
28C> using partial pivoting with row interchanges.
29C>
30C> The factorization has the form
31C> A = P * L * U
32C> where P is a permutation matrix, L is lower triangular with unit
33C> diagonal elements (lower trapezoidal if m > n), and U is upper
34C> triangular (upper trapezoidal if m < n).
35C>
36C> This is the Crout Level 3 BLAS version of the algorithm.
37C>
38C>\endverbatim
39*
40* Arguments:
41* ==========
42*
43C> \param[in] M
44C> \verbatim
45C> M is INTEGER
46C> The number of rows of the matrix A. M >= 0.
47C> \endverbatim
48C>
49C> \param[in] N
50C> \verbatim
51C> N is INTEGER
52C> The number of columns of the matrix A. N >= 0.
53C> \endverbatim
54C>
55C> \param[in,out] A
56C> \verbatim
57C> A is REAL array, dimension (LDA,N)
58C> On entry, the M-by-N matrix to be factored.
59C> On exit, the factors L and U from the factorization
60C> A = P*L*U; the unit diagonal elements of L are not stored.
61C> \endverbatim
62C>
63C> \param[in] LDA
64C> \verbatim
65C> LDA is INTEGER
66C> The leading dimension of the array A. LDA >= max(1,M).
67C> \endverbatim
68C>
69C> \param[out] IPIV
70C> \verbatim
71C> IPIV is INTEGER array, dimension (min(M,N))
72C> The pivot indices; for 1 <= i <= min(M,N), row i of the
73C> matrix was interchanged with row IPIV(i).
74C> \endverbatim
75C>
76C> \param[out] INFO
77C> \verbatim
78C> INFO is INTEGER
79C> = 0: successful exit
80C> < 0: if INFO = -i, the i-th argument had an illegal value
81C> > 0: if INFO = i, U(i,i) is exactly zero. The factorization
82C> has been completed, but the factor U is exactly
83C> singular, and division by zero will occur if it is used
84C> to solve a system of equations.
85C> \endverbatim
86C>
87*
88* Authors:
89* ========
90*
91C> \author Univ. of Tennessee
92C> \author Univ. of California Berkeley
93C> \author Univ. of Colorado Denver
94C> \author NAG Ltd.
95*
96C> \date December 2016
97*
98C> \ingroup variantsGEcomputational
99*
100* =====================================================================
101 SUBROUTINE sgetrf ( M, N, A, LDA, IPIV, INFO)
102*
103* -- LAPACK computational routine --
104* -- LAPACK is a software package provided by Univ. of Tennessee, --
105* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
106*
107* .. Scalar Arguments ..
108 INTEGER INFO, LDA, M, N
109* ..
110* .. Array Arguments ..
111 INTEGER IPIV( * )
112 REAL A( LDA, * )
113* ..
114*
115* =====================================================================
116*
117* .. Parameters ..
118 REAL ONE
119 parameter( one = 1.0e+0 )
120* ..
121* .. Local Scalars ..
122 INTEGER I, IINFO, J, JB, NB
123* ..
124* .. External Subroutines ..
125 EXTERNAL sgemm, sgetf2, slaswp, strsm, xerbla
126* ..
127* .. External Functions ..
128 INTEGER ILAENV
129 EXTERNAL ilaenv
130* ..
131* .. Intrinsic Functions ..
132 INTRINSIC max, min
133* ..
134* .. Executable Statements ..
135*
136* Test the input parameters.
137*
138 info = 0
139 IF( m.LT.0 ) THEN
140 info = -1
141 ELSE IF( n.LT.0 ) THEN
142 info = -2
143 ELSE IF( lda.LT.max( 1, m ) ) THEN
144 info = -4
145 END IF
146 IF( info.NE.0 ) THEN
147 CALL xerbla( 'SGETRF', -info )
148 RETURN
149 END IF
150*
151* Quick return if possible
152*
153 IF( m.EQ.0 .OR. n.EQ.0 )
154 $ RETURN
155*
156* Determine the block size for this environment.
157*
158 nb = ilaenv( 1, 'SGETRF', ' ', m, n, -1, -1 )
159 IF( nb.LE.1 .OR. nb.GE.min( m, n ) ) THEN
160*
161* Use unblocked code.
162*
163 CALL sgetf2( m, n, a, lda, ipiv, info )
164 ELSE
165*
166* Use blocked code.
167*
168 DO 20 j = 1, min( m, n ), nb
169 jb = min( min( m, n )-j+1, nb )
170*
171* Update current block.
172*
173 CALL sgemm( 'No transpose', 'No transpose',
174 $ m-j+1, jb, j-1, -one,
175 $ a( j, 1 ), lda, a( 1, j ), lda, one,
176 $ a( j, j ), lda )
177
178*
179* Factor diagonal and subdiagonal blocks and test for exact
180* singularity.
181*
182 CALL sgetf2( m-j+1, jb, a( j, j ), lda, ipiv( j ), iinfo )
183*
184* Adjust INFO and the pivot indices.
185*
186 IF( info.EQ.0 .AND. iinfo.GT.0 )
187 $ info = iinfo + j - 1
188 DO 10 i = j, min( m, j+jb-1 )
189 ipiv( i ) = j - 1 + ipiv( i )
190 10 CONTINUE
191*
192* Apply interchanges to column 1:J-1
193*
194 CALL slaswp( j-1, a, lda, j, j+jb-1, ipiv, 1 )
195*
196 IF ( j+jb.LE.n ) THEN
197*
198* Apply interchanges to column J+JB:N
199*
200 CALL slaswp( n-j-jb+1, a( 1, j+jb ), lda, j, j+jb-1,
201 $ ipiv, 1 )
202*
203 CALL sgemm( 'No transpose', 'No transpose',
204 $ jb, n-j-jb+1, j-1, -one,
205 $ a( j, 1 ), lda, a( 1, j+jb ), lda, one,
206 $ a( j, j+jb ), lda )
207*
208* Compute block row of U.
209*
210 CALL strsm( 'Left', 'Lower', 'No transpose', 'Unit',
211 $ jb, n-j-jb+1, one, a( j, j ), lda,
212 $ a( j, j+jb ), lda )
213 END IF
214
215 20 CONTINUE
216
217 END IF
218 RETURN
219*
220* End of SGETRF
221*
222 END
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:60
subroutine sgetrf(M, N, A, LDA, IPIV, INFO)
SGETRF
Definition: sgetrf.f:108
subroutine sgetf2(M, N, A, LDA, IPIV, INFO)
SGETF2 computes the LU factorization of a general m-by-n matrix using partial pivoting with row inter...
Definition: sgetf2.f:108
subroutine slaswp(N, A, LDA, K1, K2, IPIV, INCX)
SLASWP performs a series of row interchanges on a general rectangular matrix.
Definition: slaswp.f:115
subroutine strsm(SIDE, UPLO, TRANSA, DIAG, M, N, ALPHA, A, LDA, B, LDB)
STRSM
Definition: strsm.f:181
subroutine sgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
SGEMM
Definition: sgemm.f:187