LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
cgetrf2.f
Go to the documentation of this file.
1 *> \brief \b CGETRF2
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * RECURSIVE SUBROUTINE CGETRF2( 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 *
22 *> \par Purpose:
23 * =============
24 *>
25 *> \verbatim
26 *>
27 *> CGETRF2 computes an LU factorization of a general M-by-N matrix A
28 *> using partial pivoting with row interchanges.
29 *>
30 *> The factorization has the form
31 *> A = P * L * U
32 *> where P is a permutation matrix, L is lower triangular with unit
33 *> diagonal elements (lower trapezoidal if m > n), and U is upper
34 *> triangular (upper trapezoidal if m < n).
35 *>
36 *> This is the recursive version of the algorithm. It divides
37 *> the matrix into four submatrices:
38 *>
39 *> [ A11 | A12 ] where A11 is n1 by n1 and A22 is n2 by n2
40 *> A = [ -----|----- ] with n1 = min(m,n)/2
41 *> [ A21 | A22 ] n2 = n-n1
42 *>
43 *> [ A11 ]
44 *> The subroutine calls itself to factor [ --- ],
45 *> [ A12 ]
46 *> [ A12 ]
47 *> do the swaps on [ --- ], solve A12, update A22,
48 *> [ A22 ]
49 *>
50 *> then calls itself to factor A22 and do the swaps on A21.
51 *>
52 *> \endverbatim
53 *
54 * Arguments:
55 * ==========
56 *
57 *> \param[in] M
58 *> \verbatim
59 *> M is INTEGER
60 *> The number of rows of the matrix A. M >= 0.
61 *> \endverbatim
62 *>
63 *> \param[in] N
64 *> \verbatim
65 *> N is INTEGER
66 *> The number of columns of the matrix A. N >= 0.
67 *> \endverbatim
68 *>
69 *> \param[in,out] A
70 *> \verbatim
71 *> A is COMPLEX array, dimension (LDA,N)
72 *> On entry, the M-by-N matrix to be factored.
73 *> On exit, the factors L and U from the factorization
74 *> A = P*L*U; the unit diagonal elements of L are not stored.
75 *> \endverbatim
76 *>
77 *> \param[in] LDA
78 *> \verbatim
79 *> LDA is INTEGER
80 *> The leading dimension of the array A. LDA >= max(1,M).
81 *> \endverbatim
82 *>
83 *> \param[out] IPIV
84 *> \verbatim
85 *> IPIV is INTEGER array, dimension (min(M,N))
86 *> The pivot indices; for 1 <= i <= min(M,N), row i of the
87 *> matrix was interchanged with row IPIV(i).
88 *> \endverbatim
89 *>
90 *> \param[out] INFO
91 *> \verbatim
92 *> INFO is INTEGER
93 *> = 0: successful exit
94 *> < 0: if INFO = -i, the i-th argument had an illegal value
95 *> > 0: if INFO = i, U(i,i) is exactly zero. The factorization
96 *> has been completed, but the factor U is exactly
97 *> singular, and division by zero will occur if it is used
98 *> to solve a system of equations.
99 *> \endverbatim
100 *
101 * Authors:
102 * ========
103 *
104 *> \author Univ. of Tennessee
105 *> \author Univ. of California Berkeley
106 *> \author Univ. of Colorado Denver
107 *> \author NAG Ltd.
108 *
109 *> \date June 2016
110 *
111 *> \ingroup complexGEcomputational
112 *
113 * =====================================================================
114  RECURSIVE SUBROUTINE cgetrf2( M, N, A, LDA, IPIV, INFO )
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  COMPLEX A( lda, * )
127 * ..
128 *
129 * =====================================================================
130 *
131 * .. Parameters ..
132  COMPLEX ONE, ZERO
133  parameter ( one = ( 1.0e+0, 0.0e+0 ),
134  $ zero = ( 0.0e+0, 0.0e+0 ) )
135 * ..
136 * .. Local Scalars ..
137  REAL SFMIN
138  COMPLEX TEMP
139  INTEGER I, IINFO, N1, N2
140 * ..
141 * .. External Functions ..
142  REAL SLAMCH
143  INTEGER ICAMAX
144  EXTERNAL slamch, icamax
145 * ..
146 * .. External Subroutines ..
147  EXTERNAL cgemm, cscal, claswp, ctrsm, xerbla
148 * ..
149 * .. Intrinsic Functions ..
150  INTRINSIC max, min
151 * ..
152 * .. Executable Statements ..
153 *
154 * Test the input parameters
155 *
156  info = 0
157  IF( m.LT.0 ) THEN
158  info = -1
159  ELSE IF( n.LT.0 ) THEN
160  info = -2
161  ELSE IF( lda.LT.max( 1, m ) ) THEN
162  info = -4
163  END IF
164  IF( info.NE.0 ) THEN
165  CALL xerbla( 'CGETRF2', -info )
166  RETURN
167  END IF
168 *
169 * Quick return if possible
170 *
171  IF( m.EQ.0 .OR. n.EQ.0 )
172  $ RETURN
173 
174  IF ( m.EQ.1 ) THEN
175 *
176 * Use unblocked code for one row case
177 * Just need to handle IPIV and INFO
178 *
179  ipiv( 1 ) = 1
180  IF ( a(1,1).EQ.zero )
181  $ info = 1
182 *
183  ELSE IF( n.EQ.1 ) THEN
184 *
185 * Use unblocked code for one column case
186 *
187 *
188 * Compute machine safe minimum
189 *
190  sfmin = slamch('S')
191 *
192 * Find pivot and test for singularity
193 *
194  i = icamax( m, a( 1, 1 ), 1 )
195  ipiv( 1 ) = i
196  IF( a( i, 1 ).NE.zero ) THEN
197 *
198 * Apply the interchange
199 *
200  IF( i.NE.1 ) THEN
201  temp = a( 1, 1 )
202  a( 1, 1 ) = a( i, 1 )
203  a( i, 1 ) = temp
204  END IF
205 *
206 * Compute elements 2:M of the column
207 *
208  IF( abs(a( 1, 1 )) .GE. sfmin ) THEN
209  CALL cscal( m-1, one / a( 1, 1 ), a( 2, 1 ), 1 )
210  ELSE
211  DO 10 i = 1, m-1
212  a( 1+i, 1 ) = a( 1+i, 1 ) / a( 1, 1 )
213  10 CONTINUE
214  END IF
215 *
216  ELSE
217  info = 1
218  END IF
219 *
220  ELSE
221 *
222 * Use recursive code
223 *
224  n1 = min( m, n ) / 2
225  n2 = n-n1
226 *
227 * [ A11 ]
228 * Factor [ --- ]
229 * [ A21 ]
230 *
231  CALL cgetrf2( m, n1, a, lda, ipiv, iinfo )
232 
233  IF ( info.EQ.0 .AND. iinfo.GT.0 )
234  $ info = iinfo
235 *
236 * [ A12 ]
237 * Apply interchanges to [ --- ]
238 * [ A22 ]
239 *
240  CALL claswp( n2, a( 1, n1+1 ), lda, 1, n1, ipiv, 1 )
241 *
242 * Solve A12
243 *
244  CALL ctrsm( 'L', 'L', 'N', 'U', n1, n2, one, a, lda,
245  $ a( 1, n1+1 ), lda )
246 *
247 * Update A22
248 *
249  CALL cgemm( 'N', 'N', m-n1, n2, n1, -one, a( n1+1, 1 ), lda,
250  $ a( 1, n1+1 ), lda, one, a( n1+1, n1+1 ), lda )
251 *
252 * Factor A22
253 *
254  CALL cgetrf2( m-n1, n2, a( n1+1, n1+1 ), lda, ipiv( n1+1 ),
255  $ iinfo )
256 *
257 * Adjust INFO and the pivot indices
258 *
259  IF ( info.EQ.0 .AND. iinfo.GT.0 )
260  $ info = iinfo + n1
261  DO 20 i = n1+1, min( m, n )
262  ipiv( i ) = ipiv( i ) + n1
263  20 CONTINUE
264 *
265 * Apply interchanges to A21
266 *
267  CALL claswp( n1, a( 1, 1 ), lda, n1+1, min( m, n), ipiv, 1 )
268 *
269  END IF
270  RETURN
271 *
272 * End of CGETRF2
273 *
274  END
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine cscal(N, CA, CX, INCX)
CSCAL
Definition: cscal.f:54
subroutine ctrsm(SIDE, UPLO, TRANSA, DIAG, M, N, ALPHA, A, LDA, B, LDB)
CTRSM
Definition: ctrsm.f:182
recursive subroutine cgetrf2(M, N, A, LDA, IPIV, INFO)
CGETRF2
Definition: cgetrf2.f:115
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