LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
sgetf2.f
Go to the documentation of this file.
1 *> \brief \b SGETF2 computes the LU factorization of a general m-by-n matrix using partial pivoting with row interchanges (unblocked algorithm).
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download SGETF2 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sgetf2.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sgetf2.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sgetf2.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE SGETF2( M, N, A, LDA, IPIV, INFO )
22 *
23 * .. Scalar Arguments ..
24 * INTEGER INFO, LDA, M, N
25 * ..
26 * .. Array Arguments ..
27 * INTEGER IPIV( * )
28 * REAL A( LDA, * )
29 * ..
30 *
31 *
32 *> \par Purpose:
33 * =============
34 *>
35 *> \verbatim
36 *>
37 *> SGETF2 computes an LU factorization of a general m-by-n matrix A
38 *> using partial pivoting with row interchanges.
39 *>
40 *> The factorization has the form
41 *> A = P * L * U
42 *> where P is a permutation matrix, L is lower triangular with unit
43 *> diagonal elements (lower trapezoidal if m > n), and U is upper
44 *> triangular (upper trapezoidal if m < n).
45 *>
46 *> This is the right-looking Level 2 BLAS version of the algorithm.
47 *> \endverbatim
48 *
49 * Arguments:
50 * ==========
51 *
52 *> \param[in] M
53 *> \verbatim
54 *> M is INTEGER
55 *> The number of rows of the matrix A. M >= 0.
56 *> \endverbatim
57 *>
58 *> \param[in] N
59 *> \verbatim
60 *> N is INTEGER
61 *> The number of columns of the matrix A. N >= 0.
62 *> \endverbatim
63 *>
64 *> \param[in,out] A
65 *> \verbatim
66 *> A is REAL array, dimension (LDA,N)
67 *> On entry, the m by n matrix to be factored.
68 *> On exit, the factors L and U from the factorization
69 *> A = P*L*U; the unit diagonal elements of L are not stored.
70 *> \endverbatim
71 *>
72 *> \param[in] LDA
73 *> \verbatim
74 *> LDA is INTEGER
75 *> The leading dimension of the array A. LDA >= max(1,M).
76 *> \endverbatim
77 *>
78 *> \param[out] IPIV
79 *> \verbatim
80 *> IPIV is INTEGER array, dimension (min(M,N))
81 *> The pivot indices; for 1 <= i <= min(M,N), row i of the
82 *> matrix was interchanged with row IPIV(i).
83 *> \endverbatim
84 *>
85 *> \param[out] INFO
86 *> \verbatim
87 *> INFO is INTEGER
88 *> = 0: successful exit
89 *> < 0: if INFO = -k, the k-th argument had an illegal value
90 *> > 0: if INFO = k, U(k,k) is exactly zero. The factorization
91 *> has been completed, but the factor U is exactly
92 *> singular, and division by zero will occur if it is used
93 *> to solve a system of equations.
94 *> \endverbatim
95 *
96 * Authors:
97 * ========
98 *
99 *> \author Univ. of Tennessee
100 *> \author Univ. of California Berkeley
101 *> \author Univ. of Colorado Denver
102 *> \author NAG Ltd.
103 *
104 *> \date September 2012
105 *
106 *> \ingroup realGEcomputational
107 *
108 * =====================================================================
109  SUBROUTINE sgetf2( M, N, A, LDA, IPIV, INFO )
110 *
111 * -- LAPACK computational routine (version 3.4.2) --
112 * -- LAPACK is a software package provided by Univ. of Tennessee, --
113 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
114 * September 2012
115 *
116 * .. Scalar Arguments ..
117  INTEGER INFO, LDA, M, N
118 * ..
119 * .. Array Arguments ..
120  INTEGER IPIV( * )
121  REAL A( lda, * )
122 * ..
123 *
124 * =====================================================================
125 *
126 * .. Parameters ..
127  REAL ONE, ZERO
128  parameter ( one = 1.0e+0, zero = 0.0e+0 )
129 * ..
130 * .. Local Scalars ..
131  REAL SFMIN
132  INTEGER I, J, JP
133 * ..
134 * .. External Functions ..
135  REAL SLAMCH
136  INTEGER ISAMAX
137  EXTERNAL slamch, isamax
138 * ..
139 * .. External Subroutines ..
140  EXTERNAL sger, sscal, sswap, xerbla
141 * ..
142 * .. Intrinsic Functions ..
143  INTRINSIC max, min
144 * ..
145 * .. Executable Statements ..
146 *
147 * Test the input parameters.
148 *
149  info = 0
150  IF( m.LT.0 ) THEN
151  info = -1
152  ELSE IF( n.LT.0 ) THEN
153  info = -2
154  ELSE IF( lda.LT.max( 1, m ) ) THEN
155  info = -4
156  END IF
157  IF( info.NE.0 ) THEN
158  CALL xerbla( 'SGETF2', -info )
159  RETURN
160  END IF
161 *
162 * Quick return if possible
163 *
164  IF( m.EQ.0 .OR. n.EQ.0 )
165  $ RETURN
166 *
167 * Compute machine safe minimum
168 *
169  sfmin = slamch('S')
170 *
171  DO 10 j = 1, min( m, n )
172 *
173 * Find pivot and test for singularity.
174 *
175  jp = j - 1 + isamax( m-j+1, a( j, j ), 1 )
176  ipiv( j ) = jp
177  IF( a( jp, j ).NE.zero ) THEN
178 *
179 * Apply the interchange to columns 1:N.
180 *
181  IF( jp.NE.j )
182  $ CALL sswap( n, a( j, 1 ), lda, a( jp, 1 ), lda )
183 *
184 * Compute elements J+1:M of J-th column.
185 *
186  IF( j.LT.m ) THEN
187  IF( abs(a( j, j )) .GE. sfmin ) THEN
188  CALL sscal( m-j, one / a( j, j ), a( j+1, j ), 1 )
189  ELSE
190  DO 20 i = 1, m-j
191  a( j+i, j ) = a( j+i, j ) / a( j, j )
192  20 CONTINUE
193  END IF
194  END IF
195 *
196  ELSE IF( info.EQ.0 ) THEN
197 *
198  info = j
199  END IF
200 *
201  IF( j.LT.min( m, n ) ) THEN
202 *
203 * Update trailing submatrix.
204 *
205  CALL sger( m-j, n-j, -one, a( j+1, j ), 1, a( j, j+1 ), lda,
206  $ a( j+1, j+1 ), lda )
207  END IF
208  10 CONTINUE
209  RETURN
210 *
211 * End of SGETF2
212 *
213  END
subroutine sger(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)
SGER
Definition: sger.f:132
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:110
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine sscal(N, SA, SX, INCX)
SSCAL
Definition: sscal.f:55
subroutine sswap(N, SX, INCX, SY, INCY)
SSWAP
Definition: sswap.f:53