LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine dgetrf ( integer  M,
integer  N,
double precision, dimension( lda, * )  A,
integer  LDA,
integer, dimension( * )  IPIV,
integer  INFO 
)

DGETRF VARIANT: left-looking Level 3 BLAS version of the algorithm.

Purpose:

 DGETRF 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 left-looking Level 3 BLAS version of the algorithm.
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 DOUBLE PRECISION 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
November 2011

Definition at line 102 of file dgetrf.f.

102 *
103 * -- LAPACK computational routine (version 3.1) --
104 * -- LAPACK is a software package provided by Univ. of Tennessee, --
105 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
106 * November 2011
107 *
108 * .. Scalar Arguments ..
109  INTEGER info, lda, m, n
110 * ..
111 * .. Array Arguments ..
112  INTEGER ipiv( * )
113  DOUBLE PRECISION a( lda, * )
114 * ..
115 *
116 * =====================================================================
117 *
118 * .. Parameters ..
119  DOUBLE PRECISION one
120  parameter ( one = 1.0d+0 )
121 * ..
122 * .. Local Scalars ..
123  INTEGER i, iinfo, j, jb, k, nb
124 * ..
125 * .. External Subroutines ..
126  EXTERNAL dgemm, dgetf2, dlaswp, dtrsm, xerbla
127 * ..
128 * .. External Functions ..
129  INTEGER ilaenv
130  EXTERNAL ilaenv
131 * ..
132 * .. Intrinsic Functions ..
133  INTRINSIC max, min
134 * ..
135 * .. Executable Statements ..
136 *
137 * Test the input parameters.
138 *
139  info = 0
140  IF( m.LT.0 ) THEN
141  info = -1
142  ELSE IF( n.LT.0 ) THEN
143  info = -2
144  ELSE IF( lda.LT.max( 1, m ) ) THEN
145  info = -4
146  END IF
147  IF( info.NE.0 ) THEN
148  CALL xerbla( 'DGETRF', -info )
149  RETURN
150  END IF
151 *
152 * Quick return if possible
153 *
154  IF( m.EQ.0 .OR. n.EQ.0 )
155  $ RETURN
156 *
157 * Determine the block size for this environment.
158 *
159  nb = ilaenv( 1, 'DGETRF', ' ', m, n, -1, -1 )
160  IF( nb.LE.1 .OR. nb.GE.min( m, n ) ) THEN
161 *
162 * Use unblocked code.
163 *
164  CALL dgetf2( m, n, a, lda, ipiv, info )
165 
166  ELSE
167 *
168 * Use blocked code.
169 *
170  DO 20 j = 1, min( m, n ), nb
171  jb = min( min( m, n )-j+1, nb )
172 *
173 * Update before factoring the current panel
174 *
175  DO 30 k = 1, j-nb, nb
176 *
177 * Apply interchanges to rows K:K+NB-1.
178 *
179  CALL dlaswp( jb, a(1, j), lda, k, k+nb-1, ipiv, 1 )
180 *
181 * Compute block row of U.
182 *
183  CALL dtrsm( 'Left', 'Lower', 'No transpose', 'Unit',
184  $ nb, jb, one, a( k, k ), lda,
185  $ a( k, j ), lda )
186 *
187 * Update trailing submatrix.
188 *
189  CALL dgemm( 'No transpose', 'No transpose',
190  $ m-k-nb+1, jb, nb, -one,
191  $ a( k+nb, k ), lda, a( k, j ), lda, one,
192  $ a( k+nb, j ), lda )
193  30 CONTINUE
194 *
195 * Factor diagonal and subdiagonal blocks and test for exact
196 * singularity.
197 *
198  CALL dgetf2( m-j+1, jb, a( j, j ), lda, ipiv( j ), iinfo )
199 *
200 * Adjust INFO and the pivot indices.
201 *
202  IF( info.EQ.0 .AND. iinfo.GT.0 )
203  $ info = iinfo + j - 1
204  DO 10 i = j, min( m, j+jb-1 )
205  ipiv( i ) = j - 1 + ipiv( i )
206  10 CONTINUE
207 *
208  20 CONTINUE
209 
210 *
211 * Apply interchanges to the left-overs
212 *
213  DO 40 k = 1, min( m, n ), nb
214  CALL dlaswp( k-1, a( 1, 1 ), lda, k,
215  $ min(k+nb-1, min( m, n )), ipiv, 1 )
216  40 CONTINUE
217 *
218 * Apply update to the M+1:N columns when N > M
219 *
220  IF ( n.GT.m ) THEN
221 
222  CALL dlaswp( n-m, a(1, m+1), lda, 1, m, ipiv, 1 )
223 
224  DO 50 k = 1, m, nb
225 
226  jb = min( m-k+1, nb )
227 *
228  CALL dtrsm( 'Left', 'Lower', 'No transpose', 'Unit',
229  $ jb, n-m, one, a( k, k ), lda,
230  $ a( k, m+1 ), lda )
231 
232 *
233  IF ( k+nb.LE.m ) THEN
234  CALL dgemm( 'No transpose', 'No transpose',
235  $ m-k-nb+1, n-m, nb, -one,
236  $ a( k+nb, k ), lda, a( k, m+1 ), lda, one,
237  $ a( k+nb, m+1 ), lda )
238  END IF
239  50 CONTINUE
240  END IF
241 *
242  END IF
243  RETURN
244 *
245 * End of DGETRF
246 *
subroutine dgetf2(M, N, A, LDA, IPIV, INFO)
DGETF2 computes the LU factorization of a general m-by-n matrix using partial pivoting with row inter...
Definition: dgetf2.f:110
subroutine dtrsm(SIDE, UPLO, TRANSA, DIAG, M, N, ALPHA, A, LDA, B, LDB)
DTRSM
Definition: dtrsm.f:183
subroutine dgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
DGEMM
Definition: dgemm.f:189
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine dlaswp(N, A, LDA, K1, K2, IPIV, INCX)
DLASWP performs a series of row interchanges on a general rectangular matrix.
Definition: dlaswp.f:116
integer function ilaenv(ISPEC, NAME, OPTS, N1, N2, N3, N4)
Definition: tstiee.f:83

Here is the call graph for this function: