001:       SUBROUTINE CGETF2( M, N, A, LDA, IPIV, INFO )
002: *
003: *  -- LAPACK routine (version 3.2) --
004: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
005: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
006: *     November 2006
007: *
008: *     .. Scalar Arguments ..
009:       INTEGER            INFO, LDA, M, N
010: *     ..
011: *     .. Array Arguments ..
012:       INTEGER            IPIV( * )
013:       COMPLEX            A( LDA, * )
014: *     ..
015: *
016: *  Purpose
017: *  =======
018: *
019: *  CGETF2 computes an LU factorization of a general m-by-n matrix A
020: *  using partial pivoting with row interchanges.
021: *
022: *  The factorization has the form
023: *     A = P * L * U
024: *  where P is a permutation matrix, L is lower triangular with unit
025: *  diagonal elements (lower trapezoidal if m > n), and U is upper
026: *  triangular (upper trapezoidal if m < n).
027: *
028: *  This is the right-looking Level 2 BLAS version of the algorithm.
029: *
030: *  Arguments
031: *  =========
032: *
033: *  M       (input) INTEGER
034: *          The number of rows of the matrix A.  M >= 0.
035: *
036: *  N       (input) INTEGER
037: *          The number of columns of the matrix A.  N >= 0.
038: *
039: *  A       (input/output) COMPLEX array, dimension (LDA,N)
040: *          On entry, the m by n matrix to be factored.
041: *          On exit, the factors L and U from the factorization
042: *          A = P*L*U; the unit diagonal elements of L are not stored.
043: *
044: *  LDA     (input) INTEGER
045: *          The leading dimension of the array A.  LDA >= max(1,M).
046: *
047: *  IPIV    (output) INTEGER array, dimension (min(M,N))
048: *          The pivot indices; for 1 <= i <= min(M,N), row i of the
049: *          matrix was interchanged with row IPIV(i).
050: *
051: *  INFO    (output) INTEGER
052: *          = 0: successful exit
053: *          < 0: if INFO = -k, the k-th argument had an illegal value
054: *          > 0: if INFO = k, U(k,k) is exactly zero. The factorization
055: *               has been completed, but the factor U is exactly
056: *               singular, and division by zero will occur if it is used
057: *               to solve a system of equations.
058: *
059: *  =====================================================================
060: *
061: *     .. Parameters ..
062:       COMPLEX            ONE, ZERO
063:       PARAMETER          ( ONE = ( 1.0E+0, 0.0E+0 ),
064:      $                   ZERO = ( 0.0E+0, 0.0E+0 ) )
065: *     ..
066: *     .. Local Scalars ..
067:       REAL               SFMIN
068:       INTEGER            I, J, JP
069: *     ..
070: *     .. External Functions ..
071:       REAL               SLAMCH
072:       INTEGER            ICAMAX
073:       EXTERNAL           SLAMCH, ICAMAX
074: *     ..
075: *     .. External Subroutines ..
076:       EXTERNAL           CGERU, CSCAL, CSWAP, XERBLA
077: *     ..
078: *     .. Intrinsic Functions ..
079:       INTRINSIC          MAX, MIN
080: *     ..
081: *     .. Executable Statements ..
082: *
083: *     Test the input parameters.
084: *
085:       INFO = 0
086:       IF( M.LT.0 ) THEN
087:          INFO = -1
088:       ELSE IF( N.LT.0 ) THEN
089:          INFO = -2
090:       ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
091:          INFO = -4
092:       END IF
093:       IF( INFO.NE.0 ) THEN
094:          CALL XERBLA( 'CGETF2', -INFO )
095:          RETURN
096:       END IF
097: *
098: *     Quick return if possible
099: *
100:       IF( M.EQ.0 .OR. N.EQ.0 )
101:      $   RETURN
102: *
103: *     Compute machine safe minimum
104: *
105:       SFMIN = SLAMCH('S') 
106: *
107:       DO 10 J = 1, MIN( M, N )
108: *
109: *        Find pivot and test for singularity.
110: *
111:          JP = J - 1 + ICAMAX( M-J+1, A( J, J ), 1 )
112:          IPIV( J ) = JP
113:          IF( A( JP, J ).NE.ZERO ) THEN
114: *
115: *           Apply the interchange to columns 1:N.
116: *
117:             IF( JP.NE.J )
118:      $         CALL CSWAP( N, A( J, 1 ), LDA, A( JP, 1 ), LDA )
119: *
120: *           Compute elements J+1:M of J-th column.
121: *
122:             IF( J.LT.M ) THEN
123:                IF( ABS(A( J, J )) .GE. SFMIN ) THEN
124:                   CALL CSCAL( M-J, ONE / A( J, J ), A( J+1, J ), 1 )
125:                ELSE
126:                   DO 20 I = 1, M-J
127:                      A( J+I, J ) = A( J+I, J ) / A( J, J )
128:    20             CONTINUE
129:                END IF
130:             END IF
131: *
132:          ELSE IF( INFO.EQ.0 ) THEN
133: *
134:             INFO = J
135:          END IF
136: *
137:          IF( J.LT.MIN( M, N ) ) THEN
138: *
139: *           Update trailing submatrix.
140: *
141:             CALL CGERU( M-J, N-J, -ONE, A( J+1, J ), 1, A( J, J+1 ),
142:      $                  LDA, A( J+1, J+1 ), LDA )
143:          END IF
144:    10 CONTINUE
145:       RETURN
146: *
147: *     End of CGETF2
148: *
149:       END
150: