Annotation of rpl/lapack/lapack/zgetf2.f, revision 1.1

1.1     ! bertrand    1:       SUBROUTINE ZGETF2( M, N, A, LDA, IPIV, INFO )
        !             2: *
        !             3: *  -- LAPACK routine (version 3.2) --
        !             4: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
        !             5: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
        !             6: *     November 2006
        !             7: *
        !             8: *     .. Scalar Arguments ..
        !             9:       INTEGER            INFO, LDA, M, N
        !            10: *     ..
        !            11: *     .. Array Arguments ..
        !            12:       INTEGER            IPIV( * )
        !            13:       COMPLEX*16         A( LDA, * )
        !            14: *     ..
        !            15: *
        !            16: *  Purpose
        !            17: *  =======
        !            18: *
        !            19: *  ZGETF2 computes an LU factorization of a general m-by-n matrix A
        !            20: *  using partial pivoting with row interchanges.
        !            21: *
        !            22: *  The factorization has the form
        !            23: *     A = P * L * U
        !            24: *  where P is a permutation matrix, L is lower triangular with unit
        !            25: *  diagonal elements (lower trapezoidal if m > n), and U is upper
        !            26: *  triangular (upper trapezoidal if m < n).
        !            27: *
        !            28: *  This is the right-looking Level 2 BLAS version of the algorithm.
        !            29: *
        !            30: *  Arguments
        !            31: *  =========
        !            32: *
        !            33: *  M       (input) INTEGER
        !            34: *          The number of rows of the matrix A.  M >= 0.
        !            35: *
        !            36: *  N       (input) INTEGER
        !            37: *          The number of columns of the matrix A.  N >= 0.
        !            38: *
        !            39: *  A       (input/output) COMPLEX*16 array, dimension (LDA,N)
        !            40: *          On entry, the m by n matrix to be factored.
        !            41: *          On exit, the factors L and U from the factorization
        !            42: *          A = P*L*U; the unit diagonal elements of L are not stored.
        !            43: *
        !            44: *  LDA     (input) INTEGER
        !            45: *          The leading dimension of the array A.  LDA >= max(1,M).
        !            46: *
        !            47: *  IPIV    (output) INTEGER array, dimension (min(M,N))
        !            48: *          The pivot indices; for 1 <= i <= min(M,N), row i of the
        !            49: *          matrix was interchanged with row IPIV(i).
        !            50: *
        !            51: *  INFO    (output) INTEGER
        !            52: *          = 0: successful exit
        !            53: *          < 0: if INFO = -k, the k-th argument had an illegal value
        !            54: *          > 0: if INFO = k, U(k,k) is exactly zero. The factorization
        !            55: *               has been completed, but the factor U is exactly
        !            56: *               singular, and division by zero will occur if it is used
        !            57: *               to solve a system of equations.
        !            58: *
        !            59: *  =====================================================================
        !            60: *
        !            61: *     .. Parameters ..
        !            62:       COMPLEX*16         ONE, ZERO
        !            63:       PARAMETER          ( ONE = ( 1.0D+0, 0.0D+0 ),
        !            64:      $                   ZERO = ( 0.0D+0, 0.0D+0 ) )
        !            65: *     ..
        !            66: *     .. Local Scalars ..
        !            67:       DOUBLE PRECISION   SFMIN
        !            68:       INTEGER            I, J, JP
        !            69: *     ..
        !            70: *     .. External Functions ..
        !            71:       DOUBLE PRECISION   DLAMCH
        !            72:       INTEGER            IZAMAX
        !            73:       EXTERNAL           DLAMCH, IZAMAX
        !            74: *     ..
        !            75: *     .. External Subroutines ..
        !            76:       EXTERNAL           XERBLA, ZGERU, ZSCAL, ZSWAP
        !            77: *     ..
        !            78: *     .. Intrinsic Functions ..
        !            79:       INTRINSIC          MAX, MIN
        !            80: *     ..
        !            81: *     .. Executable Statements ..
        !            82: *
        !            83: *     Test the input parameters.
        !            84: *
        !            85:       INFO = 0
        !            86:       IF( M.LT.0 ) THEN
        !            87:          INFO = -1
        !            88:       ELSE IF( N.LT.0 ) THEN
        !            89:          INFO = -2
        !            90:       ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
        !            91:          INFO = -4
        !            92:       END IF
        !            93:       IF( INFO.NE.0 ) THEN
        !            94:          CALL XERBLA( 'ZGETF2', -INFO )
        !            95:          RETURN
        !            96:       END IF
        !            97: *
        !            98: *     Quick return if possible
        !            99: *
        !           100:       IF( M.EQ.0 .OR. N.EQ.0 )
        !           101:      $   RETURN
        !           102: *
        !           103: *     Compute machine safe minimum
        !           104: *
        !           105:       SFMIN = DLAMCH('S') 
        !           106: *
        !           107:       DO 10 J = 1, MIN( M, N )
        !           108: *
        !           109: *        Find pivot and test for singularity.
        !           110: *
        !           111:          JP = J - 1 + IZAMAX( 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 ZSWAP( 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 ZSCAL( 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 ZGERU( 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 ZGETF2
        !           148: *
        !           149:       END

CVSweb interface <joel.bertrand@systella.fr>