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

1.5       bertrand    1:       INTEGER FUNCTION ILAZLR( 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: *     .. Scalar Arguments ..
                      9:       INTEGER            M, N, LDA
                     10: *     ..
                     11: *     .. Array Arguments ..
                     12:       COMPLEX*16         A( LDA, * )
                     13: *     ..
                     14: *
                     15: *  Purpose
                     16: *  =======
                     17: *
                     18: *  ILAZLR scans A for its last non-zero row.
                     19: *
                     20: *  Arguments
                     21: *  =========
                     22: *
                     23: *  M       (input) INTEGER
                     24: *          The number of rows of the matrix A.
                     25: *
                     26: *  N       (input) INTEGER
                     27: *          The number of columns of the matrix A.
                     28: *
                     29: *  A       (input) COMPLEX*16 array, dimension (LDA,N)
                     30: *          The m by n matrix A.
                     31: *
                     32: *  LDA     (input) INTEGER
                     33: *          The leading dimension of the array A. LDA >= max(1,M).
                     34: *
                     35: *  =====================================================================
                     36: *
                     37: *     .. Parameters ..
                     38:       COMPLEX*16       ZERO
                     39:       PARAMETER ( ZERO = (0.0D+0, 0.0D+0) )
                     40: *     ..
                     41: *     .. Local Scalars ..
                     42:       INTEGER I, J
                     43: *     ..
                     44: *     .. Executable Statements ..
                     45: *
                     46: *     Quick test for the common case where one corner is non-zero.
                     47:       IF( M.EQ.0 ) THEN
                     48:          ILAZLR = M
                     49:       ELSE IF( A(M, 1).NE.ZERO .OR. A(M, N).NE.ZERO ) THEN
                     50:          ILAZLR = M
                     51:       ELSE
                     52: *     Scan up each column tracking the last zero row seen.
                     53:          ILAZLR = 0
                     54:          DO J = 1, N
1.9     ! bertrand   55:             I=M
        !            56:             DO WHILE ((A(I,J).NE.ZERO).AND.(I.GE.1))
        !            57:               I=I-1
        !            58:             ENDDO         
1.1       bertrand   59:             ILAZLR = MAX( ILAZLR, I )
                     60:          END DO
                     61:       END IF
                     62:       RETURN
1.5       bertrand   63:       END

CVSweb interface <joel.bertrand@systella.fr>