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