1       SUBROUTINE ZPBT01( UPLO, N, KD, A, LDA, AFAC, LDAFAC, RWORK,
  2      $                   RESID )
  3 *
  4 *  -- LAPACK test routine (version 3.1) --
  5 *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
  6 *     November 2006
  7 *
  8 *     .. Scalar Arguments ..
  9       CHARACTER          UPLO
 10       INTEGER            KD, LDA, LDAFAC, N
 11       DOUBLE PRECISION   RESID
 12 *     ..
 13 *     .. Array Arguments ..
 14       DOUBLE PRECISION   RWORK( * )
 15       COMPLEX*16         A( LDA, * ), AFAC( LDAFAC, * )
 16 *     ..
 17 *
 18 *  Purpose
 19 *  =======
 20 *
 21 *  ZPBT01 reconstructs a Hermitian positive definite band matrix A from
 22 *  its L*L' or U'*U factorization and computes the residual
 23 *     norm( L*L' - A ) / ( N * norm(A) * EPS ) or
 24 *     norm( U'*U - A ) / ( N * norm(A) * EPS ),
 25 *  where EPS is the machine epsilon, L' is the conjugate transpose of
 26 *  L, and U' is the conjugate transpose of U.
 27 *
 28 *  Arguments
 29 *  =========
 30 *
 31 *  UPLO    (input) CHARACTER*1
 32 *          Specifies whether the upper or lower triangular part of the
 33 *          Hermitian matrix A is stored:
 34 *          = 'U':  Upper triangular
 35 *          = 'L':  Lower triangular
 36 *
 37 *  N       (input) INTEGER
 38 *          The number of rows and columns of the matrix A.  N >= 0.
 39 *
 40 *  KD      (input) INTEGER
 41 *          The number of super-diagonals of the matrix A if UPLO = 'U',
 42 *          or the number of sub-diagonals if UPLO = 'L'.  KD >= 0.
 43 *
 44 *  A       (input) COMPLEX*16 array, dimension (LDA,N)
 45 *          The original Hermitian band matrix A.  If UPLO = 'U', the
 46 *          upper triangular part of A is stored as a band matrix; if
 47 *          UPLO = 'L', the lower triangular part of A is stored.  The
 48 *          columns of the appropriate triangle are stored in the columns
 49 *          of A and the diagonals of the triangle are stored in the rows
 50 *          of A.  See ZPBTRF for further details.
 51 *
 52 *  LDA     (input) INTEGER.
 53 *          The leading dimension of the array A.  LDA >= max(1,KD+1).
 54 *
 55 *  AFAC    (input) COMPLEX*16 array, dimension (LDAFAC,N)
 56 *          The factored form of the matrix A.  AFAC contains the factor
 57 *          L or U from the L*L' or U'*U factorization in band storage
 58 *          format, as computed by ZPBTRF.
 59 *
 60 *  LDAFAC  (input) INTEGER
 61 *          The leading dimension of the array AFAC.
 62 *          LDAFAC >= max(1,KD+1).
 63 *
 64 *  RWORK   (workspace) DOUBLE PRECISION array, dimension (N)
 65 *
 66 *  RESID   (output) DOUBLE PRECISION
 67 *          If UPLO = 'L', norm(L*L' - A) / ( N * norm(A) * EPS )
 68 *          If UPLO = 'U', norm(U'*U - A) / ( N * norm(A) * EPS )
 69 *
 70 *  =====================================================================
 71 *
 72 *
 73 *     .. Parameters ..
 74       DOUBLE PRECISION   ZERO, ONE
 75       PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
 76 *     ..
 77 *     .. Local Scalars ..
 78       INTEGER            I, J, K, KC, KLEN, ML, MU
 79       DOUBLE PRECISION   AKK, ANORM, EPS
 80 *     ..
 81 *     .. External Functions ..
 82       LOGICAL            LSAME
 83       DOUBLE PRECISION   DLAMCH, ZLANHB
 84       COMPLEX*16         ZDOTC
 85       EXTERNAL           LSAME, DLAMCH, ZLANHB, ZDOTC
 86 *     ..
 87 *     .. External Subroutines ..
 88       EXTERNAL           ZDSCAL, ZHER, ZTRMV
 89 *     ..
 90 *     .. Intrinsic Functions ..
 91       INTRINSIC          DBLEDIMAGMAXMIN
 92 *     ..
 93 *     .. Executable Statements ..
 94 *
 95 *     Quick exit if N = 0.
 96 *
 97       IF( N.LE.0 ) THEN
 98          RESID = ZERO
 99          RETURN
100       END IF
101 *
102 *     Exit with RESID = 1/EPS if ANORM = 0.
103 *
104       EPS = DLAMCH( 'Epsilon' )
105       ANORM = ZLANHB( '1', UPLO, N, KD, A, LDA, RWORK )
106       IF( ANORM.LE.ZERO ) THEN
107          RESID = ONE / EPS
108          RETURN
109       END IF
110 *
111 *     Check the imaginary parts of the diagonal elements and return with
112 *     an error code if any are nonzero.
113 *
114       IF( LSAME( UPLO, 'U' ) ) THEN
115          DO 10 J = 1, N
116             IFDIMAG( AFAC( KD+1, J ) ).NE.ZERO ) THEN
117                RESID = ONE / EPS
118                RETURN
119             END IF
120    10    CONTINUE
121       ELSE
122          DO 20 J = 1, N
123             IFDIMAG( AFAC( 1, J ) ).NE.ZERO ) THEN
124                RESID = ONE / EPS
125                RETURN
126             END IF
127    20    CONTINUE
128       END IF
129 *
130 *     Compute the product U'*U, overwriting U.
131 *
132       IF( LSAME( UPLO, 'U' ) ) THEN
133          DO 30 K = N, 1-1
134             KC = MAX1, KD+2-K )
135             KLEN = KD + 1 - KC
136 *
137 *           Compute the (K,K) element of the result.
138 *
139             AKK = ZDOTC( KLEN+1, AFAC( KC, K ), 1, AFAC( KC, K ), 1 )
140             AFAC( KD+1, K ) = AKK
141 *
142 *           Compute the rest of column K.
143 *
144             IF( KLEN.GT.0 )
145      $         CALL ZTRMV( 'Upper''Conjugate''Non-unit', KLEN,
146      $                     AFAC( KD+1, K-KLEN ), LDAFAC-1,
147      $                     AFAC( KC, K ), 1 )
148 *
149    30    CONTINUE
150 *
151 *     UPLO = 'L':  Compute the product L*L', overwriting L.
152 *
153       ELSE
154          DO 40 K = N, 1-1
155             KLEN = MIN( KD, N-K )
156 *
157 *           Add a multiple of column K of the factor L to each of
158 *           columns K+1 through N.
159 *
160             IF( KLEN.GT.0 )
161      $         CALL ZHER( 'Lower', KLEN, ONE, AFAC( 2, K ), 1,
162      $                    AFAC( 1, K+1 ), LDAFAC-1 )
163 *
164 *           Scale column K by the diagonal element.
165 *
166             AKK = AFAC( 1, K )
167             CALL ZDSCAL( KLEN+1, AKK, AFAC( 1, K ), 1 )
168 *
169    40    CONTINUE
170       END IF
171 *
172 *     Compute the difference  L*L' - A  or  U'*U - A.
173 *
174       IF( LSAME( UPLO, 'U' ) ) THEN
175          DO 60 J = 1, N
176             MU = MAX1, KD+2-J )
177             DO 50 I = MU, KD + 1
178                AFAC( I, J ) = AFAC( I, J ) - A( I, J )
179    50       CONTINUE
180    60    CONTINUE
181       ELSE
182          DO 80 J = 1, N
183             ML = MIN( KD+1, N-J+1 )
184             DO 70 I = 1, ML
185                AFAC( I, J ) = AFAC( I, J ) - A( I, J )
186    70       CONTINUE
187    80    CONTINUE
188       END IF
189 *
190 *     Compute norm( L*L' - A ) / ( N * norm(A) * EPS )
191 *
192       RESID = ZLANHB( '1', UPLO, N, KD, AFAC, LDAFAC, RWORK )
193 *
194       RESID = ( ( RESID / DBLE( N ) ) / ANORM ) / EPS
195 *
196       RETURN
197 *
198 *     End of ZPBT01
199 *
200       END