1       DOUBLE PRECISION FUNCTION DLA_RPVGRW( N, NCOLS, A, LDA, AF, LDAF )
 2 *
 3 *     -- LAPACK routine (version 3.2.2)                                 --
 4 *     -- Contributed by James Demmel, Deaglan Halligan, Yozo Hida and --
 5 *     -- Jason Riedy of Univ. of California Berkeley.                 --
 6 *     -- June 2010                                                    --
 7 *
 8 *     -- LAPACK is a software package provided by Univ. of Tennessee, --
 9 *     -- Univ. of California Berkeley and NAG Ltd.                    --
10 *
11       IMPLICIT NONE
12 *     ..
13 *     .. Scalar Arguments ..
14       INTEGER            N, NCOLS, LDA, LDAF
15 *     ..
16 *     .. Array Arguments ..
17       DOUBLE PRECISION   A( LDA, * ), AF( LDAF, * )
18 *     ..
19 *
20 *  Purpose
21 *  =======
22 
23 *  DLA_RPVGRW computes the reciprocal pivot growth factor
24 *  norm(A)/norm(U). The "max absolute element" norm is used. If this is
25 *  much less than 1, the stability of the LU factorization of the
26 *  (equilibrated) matrix A could be poor. This also means that the
27 *  solution X, estimated condition numbers, and error bounds could be
28 *  unreliable.
29 *
30 *  Arguments
31 *  =========
32 *
33 *     N       (input) INTEGER
34 *     The number of linear equations, i.e., the order of the
35 *     matrix A.  N >= 0.
36 *
37 *     NCOLS   (input) INTEGER
38 *     The number of columns of the matrix A. NCOLS >= 0.
39 *
40 *     A       (input) DOUBLE PRECISION array, dimension (LDA,N)
41 *     On entry, the N-by-N matrix A.
42 *
43 *     LDA     (input) INTEGER
44 *     The leading dimension of the array A.  LDA >= max(1,N).
45 *
46 *     AF      (input) DOUBLE PRECISION array, dimension (LDAF,N)
47 *     The factors L and U from the factorization
48 *     A = P*L*U as computed by DGETRF.
49 *
50 *     LDAF    (input) INTEGER
51 *     The leading dimension of the array AF.  LDAF >= max(1,N).
52 *
53 *  =====================================================================
54 *
55 *     .. Local Scalars ..
56       INTEGER            I, J
57       DOUBLE PRECISION   AMAX, UMAX, RPVGRW
58 *     ..
59 *     .. Intrinsic Functions ..
60       INTRINSIC          ABSMAXMIN
61 *     ..
62 *     .. Executable Statements ..
63 *
64       RPVGRW = 1.0D+0
65 
66       DO J = 1, NCOLS
67          AMAX = 0.0D+0
68          UMAX = 0.0D+0
69          DO I = 1, N
70             AMAX = MAXABS( A( I, J ) ), AMAX )
71          END DO
72          DO I = 1, J
73             UMAX = MAXABS( AF( I, J ) ), UMAX )
74          END DO
75          IF ( UMAX /= 0.0D+0 ) THEN
76             RPVGRW = MIN( AMAX / UMAX, RPVGRW )
77          END IF
78       END DO
79       DLA_RPVGRW = RPVGRW
80       END