LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dpbt01()

subroutine dpbt01 ( character  uplo,
integer  n,
integer  kd,
double precision, dimension( lda, * )  a,
integer  lda,
double precision, dimension( ldafac, * )  afac,
integer  ldafac,
double precision, dimension( * )  rwork,
double precision  resid 
)

DPBT01

Purpose:
 DPBT01 reconstructs a symmetric 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
          symmetric 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 DOUBLE PRECISION array, dimension (LDA,N)
          The original symmetric 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 DPBTRF for further details.
[in]LDA
          LDA is INTEGER.
          The leading dimension of the array A.  LDA >= max(1,KD+1).
[in]AFAC
          AFAC is DOUBLE PRECISION 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 DPBTRF.
[in]LDAFAC
          LDAFAC is INTEGER
          The leading dimension of the array AFAC.
          LDAFAC >= max(1,KD+1).
[out]RWORK
          RWORK is DOUBLE PRECISION array, dimension (N)
[out]RESID
          RESID is DOUBLE PRECISION
          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.

Definition at line 117 of file dpbt01.f.

119*
120* -- LAPACK test routine --
121* -- LAPACK is a software package provided by Univ. of Tennessee, --
122* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
123*
124* .. Scalar Arguments ..
125 CHARACTER UPLO
126 INTEGER KD, LDA, LDAFAC, N
127 DOUBLE PRECISION RESID
128* ..
129* .. Array Arguments ..
130 DOUBLE PRECISION A( LDA, * ), AFAC( LDAFAC, * ), RWORK( * )
131* ..
132*
133* =====================================================================
134*
135*
136* .. Parameters ..
137 DOUBLE PRECISION ZERO, ONE
138 parameter( zero = 0.0d+0, one = 1.0d+0 )
139* ..
140* .. Local Scalars ..
141 INTEGER I, J, K, KC, KLEN, ML, MU
142 DOUBLE PRECISION ANORM, EPS, T
143* ..
144* .. External Functions ..
145 LOGICAL LSAME
146 DOUBLE PRECISION DDOT, DLAMCH, DLANSB
147 EXTERNAL lsame, ddot, dlamch, dlansb
148* ..
149* .. External Subroutines ..
150 EXTERNAL dscal, dsyr, dtrmv
151* ..
152* .. Intrinsic Functions ..
153 INTRINSIC dble, max, min
154* ..
155* .. Executable Statements ..
156*
157* Quick exit if N = 0.
158*
159 IF( n.LE.0 ) THEN
160 resid = zero
161 RETURN
162 END IF
163*
164* Exit with RESID = 1/EPS if ANORM = 0.
165*
166 eps = dlamch( 'Epsilon' )
167 anorm = dlansb( '1', uplo, n, kd, a, lda, rwork )
168 IF( anorm.LE.zero ) THEN
169 resid = one / eps
170 RETURN
171 END IF
172*
173* Compute the product U'*U, overwriting U.
174*
175 IF( lsame( uplo, 'U' ) ) THEN
176 DO 10 k = n, 1, -1
177 kc = max( 1, kd+2-k )
178 klen = kd + 1 - kc
179*
180* Compute the (K,K) element of the result.
181*
182 t = ddot( klen+1, afac( kc, k ), 1, afac( kc, k ), 1 )
183 afac( kd+1, k ) = t
184*
185* Compute the rest of column K.
186*
187 IF( klen.GT.0 )
188 $ CALL dtrmv( 'Upper', 'Transpose', 'Non-unit', klen,
189 $ afac( kd+1, k-klen ), ldafac-1,
190 $ afac( kc, k ), 1 )
191*
192 10 CONTINUE
193*
194* UPLO = 'L': Compute the product L*L', overwriting L.
195*
196 ELSE
197 DO 20 k = n, 1, -1
198 klen = min( kd, n-k )
199*
200* Add a multiple of column K of the factor L to each of
201* columns K+1 through N.
202*
203 IF( klen.GT.0 )
204 $ CALL dsyr( 'Lower', klen, one, afac( 2, k ), 1,
205 $ afac( 1, k+1 ), ldafac-1 )
206*
207* Scale column K by the diagonal element.
208*
209 t = afac( 1, k )
210 CALL dscal( klen+1, t, afac( 1, k ), 1 )
211*
212 20 CONTINUE
213 END IF
214*
215* Compute the difference L*L' - A or U'*U - A.
216*
217 IF( lsame( uplo, 'U' ) ) THEN
218 DO 40 j = 1, n
219 mu = max( 1, kd+2-j )
220 DO 30 i = mu, kd + 1
221 afac( i, j ) = afac( i, j ) - a( i, j )
222 30 CONTINUE
223 40 CONTINUE
224 ELSE
225 DO 60 j = 1, n
226 ml = min( kd+1, n-j+1 )
227 DO 50 i = 1, ml
228 afac( i, j ) = afac( i, j ) - a( i, j )
229 50 CONTINUE
230 60 CONTINUE
231 END IF
232*
233* Compute norm( L*L' - A ) / ( N * norm(A) * EPS )
234*
235 resid = dlansb( 'I', uplo, n, kd, afac, ldafac, rwork )
236*
237 resid = ( ( resid / dble( n ) ) / anorm ) / eps
238*
239 RETURN
240*
241* End of DPBT01
242*
double precision function ddot(n, dx, incx, dy, incy)
DDOT
Definition ddot.f:82
subroutine dsyr(uplo, n, alpha, x, incx, a, lda)
DSYR
Definition dsyr.f:132
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
double precision function dlansb(norm, uplo, n, k, ab, ldab, work)
DLANSB returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
Definition dlansb.f:129
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine dscal(n, da, dx, incx)
DSCAL
Definition dscal.f:79
subroutine dtrmv(uplo, trans, diag, n, a, lda, x, incx)
DTRMV
Definition dtrmv.f:147
Here is the call graph for this function:
Here is the caller graph for this function: