001:       DOUBLE PRECISION FUNCTION ZLA_GBRPVGRW( N, KL, KU, NCOLS, AB,
002:      $                                        LDAB, AFB, LDAFB )
003: *
004: *     -- LAPACK routine (version 3.2.1)                                 --
005: *     -- Contributed by James Demmel, Deaglan Halligan, Yozo Hida and --
006: *     -- Jason Riedy of Univ. of California Berkeley.                 --
007: *     -- April 2009                                                   --
008: *
009: *     -- LAPACK is a software package provided by Univ. of Tennessee, --
010: *     -- Univ. of California Berkeley and NAG Ltd.                    --
011: *
012:       IMPLICIT NONE
013: *     ..
014: *     .. Scalar Arguments ..
015:       INTEGER            N, KL, KU, NCOLS, LDAB, LDAFB
016: *     ..
017: *     .. Array Arguments ..
018:       COMPLEX*16         AB( LDAB, * ), AFB( LDAFB, * )
019: *     ..
020: *
021: *  Purpose
022: *  =======
023: *
024: *  ZLA_GBRPVGRW computes the reciprocal pivot growth factor
025: *  norm(A)/norm(U). The "max absolute element" norm is used. If this is
026: *  much less than 1, the stability of the LU factorization of the
027: *  (equilibrated) matrix A could be poor. This also means that the
028: *  solution X, estimated condition numbers, and error bounds could be
029: *  unreliable.
030: *
031: *  Arguments
032: *  =========
033: *
034: *     N       (input) INTEGER
035: *     The number of linear equations, i.e., the order of the
036: *     matrix A.  N >= 0.
037: *
038: *     KL      (input) INTEGER
039: *     The number of subdiagonals within the band of A.  KL >= 0.
040: *
041: *     KU      (input) INTEGER
042: *     The number of superdiagonals within the band of A.  KU >= 0.
043: *
044: *     NCOLS   (input) INTEGER
045: *     The number of columns of the matrix A.  NCOLS >= 0.
046: *
047: *     AB      (input) COMPLEX*16 array, dimension (LDAB,N)
048: *     On entry, the matrix A in band storage, in rows 1 to KL+KU+1.
049: *     The j-th column of A is stored in the j-th column of the
050: *     array AB as follows:
051: *     AB(KU+1+i-j,j) = A(i,j) for max(1,j-KU)<=i<=min(N,j+kl)
052: *
053: *     LDAB    (input) INTEGER
054: *     The leading dimension of the array AB.  LDAB >= KL+KU+1.
055: *
056: *     AFB     (input) COMPLEX*16 array, dimension (LDAFB,N)
057: *     Details of the LU factorization of the band matrix A, as
058: *     computed by ZGBTRF.  U is stored as an upper triangular
059: *     band matrix with KL+KU superdiagonals in rows 1 to KL+KU+1,
060: *     and the multipliers used during the factorization are stored
061: *     in rows KL+KU+2 to 2*KL+KU+1.
062: *
063: *     LDAFB   (input) INTEGER
064: *     The leading dimension of the array AFB.  LDAFB >= 2*KL+KU+1.
065: *
066: *  =====================================================================
067: *
068: *     .. Local Scalars ..
069:       INTEGER            I, J, KD
070:       DOUBLE PRECISION   AMAX, UMAX, RPVGRW
071:       COMPLEX*16         ZDUM
072: *     ..
073: *     .. Intrinsic Functions ..
074:       INTRINSIC          ABS, MAX, MIN, REAL, DIMAG
075: *     ..
076: *     .. Statement Functions ..
077:       DOUBLE PRECISION   CABS1
078: *     ..
079: *     .. Statement Function Definitions ..
080:       CABS1( ZDUM ) = ABS( DBLE( ZDUM ) ) + ABS( DIMAG( ZDUM ) )
081: *     ..
082: *     .. Executable Statements ..
083: *
084:       RPVGRW = 1.0D+0
085: 
086:       KD = KU + 1
087:       DO J = 1, NCOLS
088:          AMAX = 0.0D+0
089:          UMAX = 0.0D+0
090:          DO I = MAX( J-KU, 1 ), MIN( J+KL, N )
091:             AMAX = MAX( CABS1( AB( KD+I-J, J ) ), AMAX )
092:          END DO
093:          DO I = MAX( J-KU, 1 ), J
094:             UMAX = MAX( CABS1( AFB( KD+I-J, J ) ), UMAX )
095:          END DO
096:          IF ( UMAX /= 0.0D+0 ) THEN
097:             RPVGRW = MIN( AMAX / UMAX, RPVGRW )
098:          END IF
099:       END DO
100:       ZLA_GBRPVGRW = RPVGRW
101:       END FUNCTION
102: