LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine cpbt01 ( character  UPLO,
integer  N,
integer  KD,
complex, dimension( lda, * )  A,
integer  LDA,
complex, dimension( ldafac, * )  AFAC,
integer  LDAFAC,
real, dimension( * )  RWORK,
real  RESID 
)

CPBT01

Purpose:
 CPBT01 reconstructs a Hermitian positive definite band matrix A from
 its L*L' or U'*U factorization and computes the residual
    norm( L*L' - A ) / ( N * norm(A) * EPS ) or
    norm( U'*U - A ) / ( N * norm(A) * EPS ),
 where EPS is the machine epsilon, L' is the conjugate transpose of
 L, and U' is the conjugate transpose of U.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          Specifies whether the upper or lower triangular part of the
          Hermitian matrix A is stored:
          = 'U':  Upper triangular
          = 'L':  Lower triangular
[in]N
          N is INTEGER
          The number of rows and columns of the matrix A.  N >= 0.
[in]KD
          KD is INTEGER
          The number of super-diagonals of the matrix A if UPLO = 'U',
          or the number of sub-diagonals if UPLO = 'L'.  KD >= 0.
[in]A
          A is COMPLEX array, dimension (LDA,N)
          The original Hermitian band matrix A.  If UPLO = 'U', the
          upper triangular part of A is stored as a band matrix; if
          UPLO = 'L', the lower triangular part of A is stored.  The
          columns of the appropriate triangle are stored in the columns
          of A and the diagonals of the triangle are stored in the rows
          of A.  See CPBTRF for further details.
[in]LDA
          LDA is INTEGER.
          The leading dimension of the array A.  LDA >= max(1,KD+1).
[in]AFAC
          AFAC is COMPLEX array, dimension (LDAFAC,N)
          The factored form of the matrix A.  AFAC contains the factor
          L or U from the L*L' or U'*U factorization in band storage
          format, as computed by CPBTRF.
[in]LDAFAC
          LDAFAC is INTEGER
          The leading dimension of the array AFAC.
          LDAFAC >= max(1,KD+1).
[out]RWORK
          RWORK is REAL array, dimension (N)
[out]RESID
          RESID is REAL
          If UPLO = 'L', norm(L*L' - A) / ( N * norm(A) * EPS )
          If UPLO = 'U', norm(U'*U - A) / ( N * norm(A) * EPS )
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 122 of file cpbt01.f.

122 *
123 * -- LAPACK test routine (version 3.4.0) --
124 * -- LAPACK is a software package provided by Univ. of Tennessee, --
125 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
126 * November 2011
127 *
128 * .. Scalar Arguments ..
129  CHARACTER uplo
130  INTEGER kd, lda, ldafac, n
131  REAL resid
132 * ..
133 * .. Array Arguments ..
134  REAL rwork( * )
135  COMPLEX a( lda, * ), afac( ldafac, * )
136 * ..
137 *
138 * =====================================================================
139 *
140 *
141 * .. Parameters ..
142  REAL zero, one
143  parameter ( zero = 0.0e+0, one = 1.0e+0 )
144 * ..
145 * .. Local Scalars ..
146  INTEGER i, j, k, kc, klen, ml, mu
147  REAL akk, anorm, eps
148 * ..
149 * .. External Functions ..
150  LOGICAL lsame
151  REAL clanhb, slamch
152  COMPLEX cdotc
153  EXTERNAL lsame, clanhb, slamch, cdotc
154 * ..
155 * .. External Subroutines ..
156  EXTERNAL cher, csscal, ctrmv
157 * ..
158 * .. Intrinsic Functions ..
159  INTRINSIC aimag, max, min, real
160 * ..
161 * .. Executable Statements ..
162 *
163 * Quick exit if N = 0.
164 *
165  IF( n.LE.0 ) THEN
166  resid = zero
167  RETURN
168  END IF
169 *
170 * Exit with RESID = 1/EPS if ANORM = 0.
171 *
172  eps = slamch( 'Epsilon' )
173  anorm = clanhb( '1', uplo, n, kd, a, lda, rwork )
174  IF( anorm.LE.zero ) THEN
175  resid = one / eps
176  RETURN
177  END IF
178 *
179 * Check the imaginary parts of the diagonal elements and return with
180 * an error code if any are nonzero.
181 *
182  IF( lsame( uplo, 'U' ) ) THEN
183  DO 10 j = 1, n
184  IF( aimag( afac( kd+1, j ) ).NE.zero ) THEN
185  resid = one / eps
186  RETURN
187  END IF
188  10 CONTINUE
189  ELSE
190  DO 20 j = 1, n
191  IF( aimag( afac( 1, j ) ).NE.zero ) THEN
192  resid = one / eps
193  RETURN
194  END IF
195  20 CONTINUE
196  END IF
197 *
198 * Compute the product U'*U, overwriting U.
199 *
200  IF( lsame( uplo, 'U' ) ) THEN
201  DO 30 k = n, 1, -1
202  kc = max( 1, kd+2-k )
203  klen = kd + 1 - kc
204 *
205 * Compute the (K,K) element of the result.
206 *
207  akk = cdotc( klen+1, afac( kc, k ), 1, afac( kc, k ), 1 )
208  afac( kd+1, k ) = akk
209 *
210 * Compute the rest of column K.
211 *
212  IF( klen.GT.0 )
213  $ CALL ctrmv( 'Upper', 'Conjugate', 'Non-unit', klen,
214  $ afac( kd+1, k-klen ), ldafac-1,
215  $ afac( kc, k ), 1 )
216 *
217  30 CONTINUE
218 *
219 * UPLO = 'L': Compute the product L*L', overwriting L.
220 *
221  ELSE
222  DO 40 k = n, 1, -1
223  klen = min( kd, n-k )
224 *
225 * Add a multiple of column K of the factor L to each of
226 * columns K+1 through N.
227 *
228  IF( klen.GT.0 )
229  $ CALL cher( 'Lower', klen, one, afac( 2, k ), 1,
230  $ afac( 1, k+1 ), ldafac-1 )
231 *
232 * Scale column K by the diagonal element.
233 *
234  akk = afac( 1, k )
235  CALL csscal( klen+1, akk, afac( 1, k ), 1 )
236 *
237  40 CONTINUE
238  END IF
239 *
240 * Compute the difference L*L' - A or U'*U - A.
241 *
242  IF( lsame( uplo, 'U' ) ) THEN
243  DO 60 j = 1, n
244  mu = max( 1, kd+2-j )
245  DO 50 i = mu, kd + 1
246  afac( i, j ) = afac( i, j ) - a( i, j )
247  50 CONTINUE
248  60 CONTINUE
249  ELSE
250  DO 80 j = 1, n
251  ml = min( kd+1, n-j+1 )
252  DO 70 i = 1, ml
253  afac( i, j ) = afac( i, j ) - a( i, j )
254  70 CONTINUE
255  80 CONTINUE
256  END IF
257 *
258 * Compute norm( L*L' - A ) / ( N * norm(A) * EPS )
259 *
260  resid = clanhb( '1', uplo, n, kd, afac, ldafac, rwork )
261 *
262  resid = ( ( resid / REAL( N ) ) / anorm ) / eps
263 *
264  RETURN
265 *
266 * End of CPBT01
267 *
subroutine cher(UPLO, N, ALPHA, X, INCX, A, LDA)
CHER
Definition: cher.f:137
complex function cdotc(N, CX, INCX, CY, INCY)
CDOTC
Definition: cdotc.f:54
subroutine ctrmv(UPLO, TRANS, DIAG, N, A, LDA, X, INCX)
CTRMV
Definition: ctrmv.f:149
real function clanhb(NORM, UPLO, N, K, AB, LDAB, WORK)
CLANHB returns the value of the 1-norm, or the Frobenius norm, or the infinity norm, or the element of largest absolute value of a Hermitian band matrix.
Definition: clanhb.f:134
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:69
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55
subroutine csscal(N, SA, CX, INCX)
CSSCAL
Definition: csscal.f:54

Here is the call graph for this function:

Here is the caller graph for this function: