LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
cgetrf.f
Go to the documentation of this file.
1 C> \brief \b CGETRF 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 CGETRF ( M, N, A, LDA, IPIV, INFO)
12 *
13 * .. Scalar Arguments ..
14 * INTEGER INFO, LDA, M, N
15 * ..
16 * .. Array Arguments ..
17 * INTEGER IPIV( * )
18 * COMPLEX A( LDA, * )
19 * ..
20 *
21 * Purpose
22 * =======
23 *
24 C>\details \b Purpose:
25 C>\verbatim
26 C>
27 C> CGETRF computes an LU factorization of a general M-by-N matrix A
28 C> using partial pivoting with row interchanges.
29 C>
30 C> The factorization has the form
31 C> A = P * L * U
32 C> where P is a permutation matrix, L is lower triangular with unit
33 C> diagonal elements (lower trapezoidal if m > n), and U is upper
34 C> triangular (upper trapezoidal if m < n).
35 C>
36 C> This is the Crout Level 3 BLAS version of the algorithm.
37 C>
38 C>\endverbatim
39 *
40 * Arguments:
41 * ==========
42 *
43 C> \param[in] M
44 C> \verbatim
45 C> M is INTEGER
46 C> The number of rows of the matrix A. M >= 0.
47 C> \endverbatim
48 C>
49 C> \param[in] N
50 C> \verbatim
51 C> N is INTEGER
52 C> The number of columns of the matrix A. N >= 0.
53 C> \endverbatim
54 C>
55 C> \param[in,out] A
56 C> \verbatim
57 C> A is COMPLEX array, dimension (LDA,N)
58 C> On entry, the M-by-N matrix to be factored.
59 C> On exit, the factors L and U from the factorization
60 C> A = P*L*U; the unit diagonal elements of L are not stored.
61 C> \endverbatim
62 C>
63 C> \param[in] LDA
64 C> \verbatim
65 C> LDA is INTEGER
66 C> The leading dimension of the array A. LDA >= max(1,M).
67 C> \endverbatim
68 C>
69 C> \param[out] IPIV
70 C> \verbatim
71 C> IPIV is INTEGER array, dimension (min(M,N))
72 C> The pivot indices; for 1 <= i <= min(M,N), row i of the
73 C> matrix was interchanged with row IPIV(i).
74 C> \endverbatim
75 C>
76 C> \param[out] INFO
77 C> \verbatim
78 C> INFO is INTEGER
79 C> = 0: successful exit
80 C> < 0: if INFO = -i, the i-th argument had an illegal value
81 C> > 0: if INFO = i, U(i,i) is exactly zero. The factorization
82 C> has been completed, but the factor U is exactly
83 C> singular, and division by zero will occur if it is used
84 C> to solve a system of equations.
85 C> \endverbatim
86 C>
87 *
88 * Authors:
89 * ========
90 *
91 C> \author Univ. of Tennessee
92 C> \author Univ. of California Berkeley
93 C> \author Univ. of Colorado Denver
94 C> \author NAG Ltd.
95 *
96 C> \date November 2011
97 *
98 C> \ingroup variantsGEcomputational
99 *
100 * =====================================================================
101  SUBROUTINE cgetrf ( M, N, A, LDA, IPIV, INFO)
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  COMPLEX A( lda, * )
114 * ..
115 *
116 * =====================================================================
117 *
118 * .. Parameters ..
119  COMPLEX ONE
120  parameter ( one = ( 1.0e+0, 0.0e+0 ) )
121 * ..
122 * .. Local Scalars ..
123  INTEGER I, IINFO, J, JB, NB
124 * ..
125 * .. External Subroutines ..
126  EXTERNAL cgemm, cgetf2, claswp, ctrsm, 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( 'CGETRF', -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, 'CGETRF', ' ', m, n, -1, -1 )
160  IF( nb.LE.1 .OR. nb.GE.min( m, n ) ) THEN
161 *
162 * Use unblocked code.
163 *
164  CALL cgetf2( m, n, a, lda, ipiv, info )
165  ELSE
166 *
167 * Use blocked code.
168 *
169  DO 20 j = 1, min( m, n ), nb
170  jb = min( min( m, n )-j+1, nb )
171 *
172 * Update current block.
173 *
174  CALL cgemm( 'No transpose', 'No transpose',
175  $ m-j+1, jb, j-1, -one,
176  $ a( j, 1 ), lda, a( 1, j ), lda, one,
177  $ a( j, j ), lda )
178 
179 *
180 * Factor diagonal and subdiagonal blocks and test for exact
181 * singularity.
182 *
183  CALL cgetf2( m-j+1, jb, a( j, j ), lda, ipiv( j ), iinfo )
184 *
185 * Adjust INFO and the pivot indices.
186 *
187  IF( info.EQ.0 .AND. iinfo.GT.0 )
188  $ info = iinfo + j - 1
189  DO 10 i = j, min( m, j+jb-1 )
190  ipiv( i ) = j - 1 + ipiv( i )
191  10 CONTINUE
192 *
193 * Apply interchanges to column 1:J-1
194 *
195  CALL claswp( j-1, a, lda, j, j+jb-1, ipiv, 1 )
196 *
197  IF ( j+jb.LE.n ) THEN
198 *
199 * Apply interchanges to column J+JB:N
200 *
201  CALL claswp( n-j-jb+1, a( 1, j+jb ), lda, j, j+jb-1,
202  $ ipiv, 1 )
203 *
204  CALL cgemm( 'No transpose', 'No transpose',
205  $ jb, n-j-jb+1, j-1, -one,
206  $ a( j, 1 ), lda, a( 1, j+jb ), lda, one,
207  $ a( j, j+jb ), lda )
208 *
209 * Compute block row of U.
210 *
211  CALL ctrsm( 'Left', 'Lower', 'No transpose', 'Unit',
212  $ jb, n-j-jb+1, one, a( j, j ), lda,
213  $ a( j, j+jb ), lda )
214  END IF
215 
216  20 CONTINUE
217 
218  END IF
219  RETURN
220 *
221 * End of CGETRF
222 *
223  END
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine ctrsm(SIDE, UPLO, TRANSA, DIAG, M, N, ALPHA, A, LDA, B, LDB)
CTRSM
Definition: ctrsm.f:182
subroutine cgetrf(M, N, A, LDA, IPIV, INFO)
CGETRF
Definition: cgetrf.f:110
subroutine cgetf2(M, N, A, LDA, IPIV, INFO)
CGETF2 computes the LU factorization of a general m-by-n matrix using partial pivoting with row inter...
Definition: cgetf2.f:110
subroutine cgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
CGEMM
Definition: cgemm.f:189
subroutine claswp(N, A, LDA, K1, K2, IPIV, INCX)
CLASWP performs a series of row interchanges on a general rectangular matrix.
Definition: claswp.f:116