001:       SUBROUTINE SGETF2( 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:       REAL               A( LDA, * )
014: *     ..
015: *
016: *  Purpose
017: *  =======
018: *
019: *  SGETF2 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) REAL 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:       REAL               ONE, ZERO
063:       PARAMETER          ( ONE = 1.0E+0, ZERO = 0.0E+0 )
064: *     ..
065: *     .. Local Scalars ..
066:       REAL               SFMIN
067:       INTEGER            I, J, JP
068: *     ..
069: *     .. External Functions ..
070:       REAL               SLAMCH
071:       INTEGER            ISAMAX
072:       EXTERNAL           SLAMCH, ISAMAX
073: *     ..
074: *     .. External Subroutines ..
075:       EXTERNAL           SGER, SSCAL, SSWAP, XERBLA
076: *     ..
077: *     .. Intrinsic Functions ..
078:       INTRINSIC          MAX, MIN
079: *     ..
080: *     .. Executable Statements ..
081: *
082: *     Test the input parameters.
083: *
084:       INFO = 0
085:       IF( M.LT.0 ) THEN
086:          INFO = -1
087:       ELSE IF( N.LT.0 ) THEN
088:          INFO = -2
089:       ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
090:          INFO = -4
091:       END IF
092:       IF( INFO.NE.0 ) THEN
093:          CALL XERBLA( 'SGETF2', -INFO )
094:          RETURN
095:       END IF
096: *
097: *     Quick return if possible
098: *
099:       IF( M.EQ.0 .OR. N.EQ.0 )
100:      $   RETURN
101: *
102: *     Compute machine safe minimum 
103: * 
104:       SFMIN = SLAMCH('S')
105: *
106:       DO 10 J = 1, MIN( M, N )
107: *
108: *        Find pivot and test for singularity.
109: *
110:          JP = J - 1 + ISAMAX( M-J+1, A( J, J ), 1 )
111:          IPIV( J ) = JP
112:          IF( A( JP, J ).NE.ZERO ) THEN
113: *
114: *           Apply the interchange to columns 1:N.
115: *
116:             IF( JP.NE.J )
117:      $         CALL SSWAP( N, A( J, 1 ), LDA, A( JP, 1 ), LDA )
118: *
119: *           Compute elements J+1:M of J-th column.
120: *
121:             IF( J.LT.M ) THEN 
122:                IF( ABS(A( J, J )) .GE. SFMIN ) THEN 
123:                   CALL SSCAL( M-J, ONE / A( J, J ), A( J+1, J ), 1 ) 
124:                ELSE 
125:                  DO 20 I = 1, M-J 
126:                     A( J+I, J ) = A( J+I, J ) / A( J, J ) 
127:    20            CONTINUE 
128:                END IF 
129:             END IF 
130: *
131:          ELSE IF( INFO.EQ.0 ) THEN
132: *
133:             INFO = J
134:          END IF
135: *
136:          IF( J.LT.MIN( M, N ) ) THEN
137: *
138: *           Update trailing submatrix.
139: *
140:             CALL SGER( M-J, N-J, -ONE, A( J+1, J ), 1, A( J, J+1 ), LDA,
141:      $                 A( J+1, J+1 ), LDA )
142:          END IF
143:    10 CONTINUE
144:       RETURN
145: *
146: *     End of SGETF2
147: *
148:       END
149: