Statistiques
| Révision :

root / src / lapack / util / iladlr.f @ 8

Historique | Voir | Annoter | Télécharger (1,47 ko)

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