Annotation of rpl/lapack/lapack/iladlr.f, revision 1.9

1.5       bertrand    1:       INTEGER FUNCTION ILADLR( M, N, A, LDA )
1.1       bertrand    2:       IMPLICIT NONE
                      3: *
1.9     ! bertrand    4: *  -- LAPACK auxiliary routine (version 3.3.1)                        --
1.1       bertrand    5: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
                      6: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
1.9     ! bertrand    7: *  -- April 2011                                                      --
1.1       bertrand    8: *
                      9: *     .. Scalar Arguments ..
                     10:       INTEGER            M, N, LDA
                     11: *     ..
                     12: *     .. Array Arguments ..
                     13:       DOUBLE PRECISION   A( LDA, * )
                     14: *     ..
                     15: *
                     16: *  Purpose
                     17: *  =======
                     18: *
                     19: *  ILADLR scans A for its last non-zero row.
                     20: *
                     21: *  Arguments
                     22: *  =========
                     23: *
                     24: *  M       (input) INTEGER
                     25: *          The number of rows of the matrix A.
                     26: *
                     27: *  N       (input) INTEGER
                     28: *          The number of columns of the matrix A.
                     29: *
                     30: *  A       (input) DOUBLE PRECISION array, dimension (LDA,N)
                     31: *          The m by n matrix A.
                     32: *
                     33: *  LDA     (input) INTEGER
                     34: *          The leading dimension of the array A. LDA >= max(1,M).
                     35: *
                     36: *  =====================================================================
                     37: *
                     38: *     .. Parameters ..
                     39:       DOUBLE PRECISION ZERO
                     40:       PARAMETER ( ZERO = 0.0D+0 )
                     41: *     ..
                     42: *     .. Local Scalars ..
                     43:       INTEGER I, J
                     44: *     ..
                     45: *     .. Executable Statements ..
                     46: *
                     47: *     Quick test for the common case where one corner is non-zero.
                     48:       IF( M.EQ.0 ) THEN
                     49:          ILADLR = M
                     50:       ELSE IF( A(M, 1).NE.ZERO .OR. A(M, N).NE.ZERO ) THEN
                     51:          ILADLR = M
                     52:       ELSE
                     53: *     Scan up each column tracking the last zero row seen.
                     54:          ILADLR = 0
                     55:          DO J = 1, N
1.9     ! bertrand   56:             I=M
        !            57:             DO WHILE ((A(I,J).NE.ZERO).AND.(I.GE.1))
        !            58:               I=I-1
        !            59:             ENDDO
1.1       bertrand   60:             ILADLR = MAX( ILADLR, I )
                     61:          END DO
                     62:       END IF
                     63:       RETURN
1.5       bertrand   64:       END

CVSweb interface <joel.bertrand@systella.fr>