LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine zgetf2 ( integer  M,
integer  N,
complex*16, dimension( lda, * )  A,
integer  LDA,
integer, dimension( * )  IPIV,
integer  INFO 
)

ZGETF2 computes the LU factorization of a general m-by-n matrix using partial pivoting with row interchanges (unblocked algorithm).

Download ZGETF2 + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 ZGETF2 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 right-looking Level 2 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 COMPLEX*16 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 = -k, the k-th argument had an illegal value
          > 0: if INFO = k, U(k,k) 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
September 2012

Definition at line 110 of file zgetf2.f.

110 *
111 * -- LAPACK computational routine (version 3.4.2) --
112 * -- LAPACK is a software package provided by Univ. of Tennessee, --
113 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
114 * September 2012
115 *
116 * .. Scalar Arguments ..
117  INTEGER info, lda, m, n
118 * ..
119 * .. Array Arguments ..
120  INTEGER ipiv( * )
121  COMPLEX*16 a( lda, * )
122 * ..
123 *
124 * =====================================================================
125 *
126 * .. Parameters ..
127  COMPLEX*16 one, zero
128  parameter ( one = ( 1.0d+0, 0.0d+0 ),
129  $ zero = ( 0.0d+0, 0.0d+0 ) )
130 * ..
131 * .. Local Scalars ..
132  DOUBLE PRECISION sfmin
133  INTEGER i, j, jp
134 * ..
135 * .. External Functions ..
136  DOUBLE PRECISION dlamch
137  INTEGER izamax
138  EXTERNAL dlamch, izamax
139 * ..
140 * .. External Subroutines ..
141  EXTERNAL xerbla, zgeru, zscal, zswap
142 * ..
143 * .. Intrinsic Functions ..
144  INTRINSIC max, min
145 * ..
146 * .. Executable Statements ..
147 *
148 * Test the input parameters.
149 *
150  info = 0
151  IF( m.LT.0 ) THEN
152  info = -1
153  ELSE IF( n.LT.0 ) THEN
154  info = -2
155  ELSE IF( lda.LT.max( 1, m ) ) THEN
156  info = -4
157  END IF
158  IF( info.NE.0 ) THEN
159  CALL xerbla( 'ZGETF2', -info )
160  RETURN
161  END IF
162 *
163 * Quick return if possible
164 *
165  IF( m.EQ.0 .OR. n.EQ.0 )
166  $ RETURN
167 *
168 * Compute machine safe minimum
169 *
170  sfmin = dlamch('S')
171 *
172  DO 10 j = 1, min( m, n )
173 *
174 * Find pivot and test for singularity.
175 *
176  jp = j - 1 + izamax( m-j+1, a( j, j ), 1 )
177  ipiv( j ) = jp
178  IF( a( jp, j ).NE.zero ) THEN
179 *
180 * Apply the interchange to columns 1:N.
181 *
182  IF( jp.NE.j )
183  $ CALL zswap( n, a( j, 1 ), lda, a( jp, 1 ), lda )
184 *
185 * Compute elements J+1:M of J-th column.
186 *
187  IF( j.LT.m ) THEN
188  IF( abs(a( j, j )) .GE. sfmin ) THEN
189  CALL zscal( m-j, one / a( j, j ), a( j+1, j ), 1 )
190  ELSE
191  DO 20 i = 1, m-j
192  a( j+i, j ) = a( j+i, j ) / a( j, j )
193  20 CONTINUE
194  END IF
195  END IF
196 *
197  ELSE IF( info.EQ.0 ) THEN
198 *
199  info = j
200  END IF
201 *
202  IF( j.LT.min( m, n ) ) THEN
203 *
204 * Update trailing submatrix.
205 *
206  CALL zgeru( m-j, n-j, -one, a( j+1, j ), 1, a( j, j+1 ),
207  $ lda, a( j+1, j+1 ), lda )
208  END IF
209  10 CONTINUE
210  RETURN
211 *
212 * End of ZGETF2
213 *
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:65
subroutine zswap(N, ZX, INCX, ZY, INCY)
ZSWAP
Definition: zswap.f:52
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
integer function izamax(N, ZX, INCX)
IZAMAX
Definition: izamax.f:53
subroutine zgeru(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)
ZGERU
Definition: zgeru.f:132
subroutine zscal(N, ZA, ZX, INCX)
ZSCAL
Definition: zscal.f:54

Here is the call graph for this function:

Here is the caller graph for this function: