LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
recursive subroutine sgetrf2 ( integer  M,
integer  N,
real, dimension( lda, * )  A,
integer  LDA,
integer, dimension( * )  IPIV,
integer  INFO 
)

SGETRF2

Purpose:
 SGETRF2 computes an LU factorization of a general M-by-N matrix A
 using partial pivoting with row interchanges.

 The factorization has the form
    A = P * L * U
 where P is a permutation matrix, L is lower triangular with unit
 diagonal elements (lower trapezoidal if m > n), and U is upper
 triangular (upper trapezoidal if m < n).

 This is the recursive version of the algorithm. It divides
 the matrix into four submatrices:
            
        [  A11 | A12  ]  where A11 is n1 by n1 and A22 is n2 by n2
    A = [ --&mdash;|--&mdash; ]  with n1 = min(m,n)/2             
                                       [ A11 ]
 The subroutine calls itself to factor [ --- ],
                                       [ A12 ]
                 [ A12 ]
 do the swaps on [ --- ], solve A12, update A22,
                 [ A22 ]

 then calls itself to factor A22 and do the swaps on A21.
Parameters
[in]M
          M is INTEGER
          The number of rows of the matrix A.  M >= 0.
[in]N
          N is INTEGER
          The number of columns of the matrix A.  N >= 0.
[in,out]A
          A is REAL array, dimension (LDA,N)
          On entry, the M-by-N matrix to be factored.
          On exit, the factors L and U from the factorization
          A = P*L*U; the unit diagonal elements of L are not stored.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,M).
[out]IPIV
          IPIV is INTEGER array, dimension (min(M,N))
          The pivot indices; for 1 <= i <= min(M,N), row i of the
          matrix was interchanged with row IPIV(i).
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0:  if INFO = -i, the i-th argument had an illegal value
          > 0:  if INFO = i, U(i,i) is exactly zero. The factorization
                has been completed, but the factor U is exactly
                singular, and division by zero will occur if it is used
                to solve a system of equations.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
June 2016

Definition at line 115 of file sgetrf2.f.

115 *
116 * -- LAPACK computational routine (version 3.6.1) --
117 * -- LAPACK is a software package provided by Univ. of Tennessee, --
118 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
119 * June 2016
120 *
121 * .. Scalar Arguments ..
122  INTEGER info, lda, m, n
123 * ..
124 * .. Array Arguments ..
125  INTEGER ipiv( * )
126  REAL a( lda, * )
127 * ..
128 *
129 * =====================================================================
130 *
131 * .. Parameters ..
132  REAL one, zero
133  parameter ( one = 1.0e+0, zero = 0.0e+0 )
134 * ..
135 * .. Local Scalars ..
136  REAL sfmin, temp
137  INTEGER i, iinfo, n1, n2
138 * ..
139 * .. External Functions ..
140  REAL slamch
141  INTEGER isamax
142  EXTERNAL slamch, isamax
143 * ..
144 * .. External Subroutines ..
145  EXTERNAL sgemm, sscal, slaswp, strsm, xerbla
146 * ..
147 * .. Intrinsic Functions ..
148  INTRINSIC max, min
149 * ..
150 * .. Executable Statements ..
151 *
152 * Test the input parameters
153 *
154  info = 0
155  IF( m.LT.0 ) THEN
156  info = -1
157  ELSE IF( n.LT.0 ) THEN
158  info = -2
159  ELSE IF( lda.LT.max( 1, m ) ) THEN
160  info = -4
161  END IF
162  IF( info.NE.0 ) THEN
163  CALL xerbla( 'SGETRF2', -info )
164  RETURN
165  END IF
166 *
167 * Quick return if possible
168 *
169  IF( m.EQ.0 .OR. n.EQ.0 )
170  $ RETURN
171 
172  IF ( m.EQ.1 ) THEN
173 *
174 * Use unblocked code for one row case
175 * Just need to handle IPIV and INFO
176 *
177  ipiv( 1 ) = 1
178  IF ( a(1,1).EQ.zero )
179  $ info = 1
180 *
181  ELSE IF( n.EQ.1 ) THEN
182 *
183 * Use unblocked code for one column case
184 *
185 *
186 * Compute machine safe minimum
187 *
188  sfmin = slamch('S')
189 *
190 * Find pivot and test for singularity
191 *
192  i = isamax( m, a( 1, 1 ), 1 )
193  ipiv( 1 ) = i
194  IF( a( i, 1 ).NE.zero ) THEN
195 *
196 * Apply the interchange
197 *
198  IF( i.NE.1 ) THEN
199  temp = a( 1, 1 )
200  a( 1, 1 ) = a( i, 1 )
201  a( i, 1 ) = temp
202  END IF
203 *
204 * Compute elements 2:M of the column
205 *
206  IF( abs(a( 1, 1 )) .GE. sfmin ) THEN
207  CALL sscal( m-1, one / a( 1, 1 ), a( 2, 1 ), 1 )
208  ELSE
209  DO 10 i = 1, m-1
210  a( 1+i, 1 ) = a( 1+i, 1 ) / a( 1, 1 )
211  10 CONTINUE
212  END IF
213 *
214  ELSE
215  info = 1
216  END IF
217 *
218  ELSE
219 *
220 * Use recursive code
221 *
222  n1 = min( m, n ) / 2
223  n2 = n-n1
224 *
225 * [ A11 ]
226 * Factor [ --- ]
227 * [ A21 ]
228 *
229  CALL sgetrf2( m, n1, a, lda, ipiv, iinfo )
230 
231  IF ( info.EQ.0 .AND. iinfo.GT.0 )
232  $ info = iinfo
233 *
234 * [ A12 ]
235 * Apply interchanges to [ --- ]
236 * [ A22 ]
237 *
238  CALL slaswp( n2, a( 1, n1+1 ), lda, 1, n1, ipiv, 1 )
239 *
240 * Solve A12
241 *
242  CALL strsm( 'L', 'L', 'N', 'U', n1, n2, one, a, lda,
243  $ a( 1, n1+1 ), lda )
244 *
245 * Update A22
246 *
247  CALL sgemm( 'N', 'N', m-n1, n2, n1, -one, a( n1+1, 1 ), lda,
248  $ a( 1, n1+1 ), lda, one, a( n1+1, n1+1 ), lda )
249 *
250 * Factor A22
251 *
252  CALL sgetrf2( m-n1, n2, a( n1+1, n1+1 ), lda, ipiv( n1+1 ),
253  $ iinfo )
254 *
255 * Adjust INFO and the pivot indices
256 *
257  IF ( info.EQ.0 .AND. iinfo.GT.0 )
258  $ info = iinfo + n1
259  DO 20 i = n1+1, min( m, n )
260  ipiv( i ) = ipiv( i ) + n1
261  20 CONTINUE
262 *
263 * Apply interchanges to A21
264 *
265  CALL slaswp( n1, a( 1, 1 ), lda, n1+1, min( m, n), ipiv, 1 )
266 *
267  END IF
268  RETURN
269 *
270 * End of SGETRF2
271 *
subroutine strsm(SIDE, UPLO, TRANSA, DIAG, M, N, ALPHA, A, LDA, B, LDB)
STRSM
Definition: strsm.f:183
integer function isamax(N, SX, INCX)
ISAMAX
Definition: isamax.f:53
subroutine sgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
SGEMM
Definition: sgemm.f:189
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine slaswp(N, A, LDA, K1, K2, IPIV, INCX)
SLASWP performs a series of row interchanges on a general rectangular matrix.
Definition: slaswp.f:116
recursive subroutine sgetrf2(M, N, A, LDA, IPIV, INFO)
SGETRF2
Definition: sgetrf2.f:115
subroutine sscal(N, SA, SX, INCX)
SSCAL
Definition: sscal.f:55
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:69

Here is the call graph for this function:

Here is the caller graph for this function: