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

◆ dgbt02()

subroutine dgbt02 ( character  trans,
integer  m,
integer  n,
integer  kl,
integer  ku,
integer  nrhs,
double precision, dimension( lda, * )  a,
integer  lda,
double precision, dimension( ldx, * )  x,
integer  ldx,
double precision, dimension( ldb, * )  b,
integer  ldb,
double precision, dimension( * )  rwork,
double precision  resid 
)

DGBT02

Purpose:
 DGBT02 computes the residual for a solution of a banded system of
 equations op(A)*X = B:
    RESID = norm(B - op(A)*X) / ( norm(op(A)) * norm(X) * EPS ),
 where op(A) = A or A**T, depending on TRANS, and EPS is the
 machine epsilon.
 The norm used is the 1-norm.
Parameters
[in]TRANS
          TRANS is CHARACTER*1
          Specifies the form of the system of equations:
          = 'N':  A    * X = B  (No transpose)
          = 'T':  A**T * X = B  (Transpose)
          = 'C':  A**H * X = B  (Conjugate transpose = Transpose)
[in]M
          M is INTEGER
          The number of rows of the matrix A.  M >= 0.
[in]N
          N is INTEGER
          The number of columns of the matrix A.  N >= 0.
[in]KL
          KL is INTEGER
          The number of subdiagonals within the band of A.  KL >= 0.
[in]KU
          KU is INTEGER
          The number of superdiagonals within the band of A.  KU >= 0.
[in]NRHS
          NRHS is INTEGER
          The number of columns of B.  NRHS >= 0.
[in]A
          A is DOUBLE PRECISION array, dimension (LDA,N)
          The original matrix A in band storage, stored in rows 1 to
          KL+KU+1.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,KL+KU+1).
[in]X
          X is DOUBLE PRECISION array, dimension (LDX,NRHS)
          The computed solution vectors for the system of linear
          equations.
[in]LDX
          LDX is INTEGER
          The leading dimension of the array X.  If TRANS = 'N',
          LDX >= max(1,N); if TRANS = 'T' or 'C', LDX >= max(1,M).
[in,out]B
          B is DOUBLE PRECISION array, dimension (LDB,NRHS)
          On entry, the right hand side vectors for the system of
          linear equations.
          On exit, B is overwritten with the difference B - A*X.
[in]LDB
          LDB is INTEGER
          The leading dimension of the array B.  IF TRANS = 'N',
          LDB >= max(1,M); if TRANS = 'T' or 'C', LDB >= max(1,N).
[out]RWORK
          RWORK is DOUBLE PRECISION array, dimension (MAX(1,LRWORK)),
          where LRWORK >= M when TRANS = 'T' or 'C'; otherwise, RWORK
          is not referenced.
[out]RESID
          RESID is DOUBLE PRECISION
          The maximum over the number of right hand sides of
          norm(B - op(A)*X) / ( norm(op(A)) * norm(X) * EPS ).
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 147 of file dgbt02.f.

149*
150* -- LAPACK test routine --
151* -- LAPACK is a software package provided by Univ. of Tennessee, --
152* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
153*
154* .. Scalar Arguments ..
155 CHARACTER TRANS
156 INTEGER KL, KU, LDA, LDB, LDX, M, N, NRHS
157 DOUBLE PRECISION RESID
158* ..
159* .. Array Arguments ..
160 DOUBLE PRECISION A( LDA, * ), B( LDB, * ), X( LDX, * ),
161 $ RWORK( * )
162* ..
163*
164* =====================================================================
165*
166* .. Parameters ..
167 DOUBLE PRECISION ZERO, ONE
168 parameter( zero = 0.0d+0, one = 1.0d+0 )
169* ..
170* .. Local Scalars ..
171 INTEGER I1, I2, J, KD, N1
172 DOUBLE PRECISION ANORM, BNORM, EPS, TEMP, XNORM
173* ..
174* .. External Functions ..
175 LOGICAL DISNAN, LSAME
176 DOUBLE PRECISION DASUM, DLAMCH
177 EXTERNAL dasum, disnan, dlamch, lsame
178* ..
179* .. External Subroutines ..
180 EXTERNAL dgbmv
181* ..
182* .. Intrinsic Functions ..
183 INTRINSIC abs, max, min
184* ..
185* .. Executable Statements ..
186*
187* Quick return if N = 0 pr NRHS = 0
188*
189 IF( m.LE.0 .OR. n.LE.0 .OR. nrhs.LE.0 ) THEN
190 resid = zero
191 RETURN
192 END IF
193*
194* Exit with RESID = 1/EPS if ANORM = 0.
195*
196 eps = dlamch( 'Epsilon' )
197 anorm = zero
198 IF( lsame( trans, 'N' ) ) THEN
199*
200* Find norm1(A).
201*
202 kd = ku + 1
203 DO 10 j = 1, n
204 i1 = max( kd+1-j, 1 )
205 i2 = min( kd+m-j, kl+kd )
206 IF( i2.GE.i1 ) THEN
207 temp = dasum( i2-i1+1, a( i1, j ), 1 )
208 IF( anorm.LT.temp .OR. disnan( temp ) ) anorm = temp
209 END IF
210 10 CONTINUE
211 ELSE
212*
213* Find normI(A).
214*
215 DO 12 i1 = 1, m
216 rwork( i1 ) = zero
217 12 CONTINUE
218 DO 16 j = 1, n
219 kd = ku + 1 - j
220 DO 14 i1 = max( 1, j-ku ), min( m, j+kl )
221 rwork( i1 ) = rwork( i1 ) + abs( a( kd+i1, j ) )
222 14 CONTINUE
223 16 CONTINUE
224 DO 18 i1 = 1, m
225 temp = rwork( i1 )
226 IF( anorm.LT.temp .OR. disnan( temp ) ) anorm = temp
227 18 CONTINUE
228 END IF
229 IF( anorm.LE.zero ) THEN
230 resid = one / eps
231 RETURN
232 END IF
233*
234 IF( lsame( trans, 'T' ) .OR. lsame( trans, 'C' ) ) THEN
235 n1 = n
236 ELSE
237 n1 = m
238 END IF
239*
240* Compute B - op(A)*X
241*
242 DO 20 j = 1, nrhs
243 CALL dgbmv( trans, m, n, kl, ku, -one, a, lda, x( 1, j ), 1,
244 $ one, b( 1, j ), 1 )
245 20 CONTINUE
246*
247* Compute the maximum over the number of right hand sides of
248* norm(B - op(A)*X) / ( norm(op(A)) * norm(X) * EPS ).
249*
250 resid = zero
251 DO 30 j = 1, nrhs
252 bnorm = dasum( n1, b( 1, j ), 1 )
253 xnorm = dasum( n1, x( 1, j ), 1 )
254 IF( xnorm.LE.zero ) THEN
255 resid = one / eps
256 ELSE
257 resid = max( resid, ( ( bnorm / anorm ) / xnorm ) / eps )
258 END IF
259 30 CONTINUE
260*
261 RETURN
262*
263* End of DGBT02
264*
double precision function dasum(n, dx, incx)
DASUM
Definition dasum.f:71
subroutine dgbmv(trans, m, n, kl, ku, alpha, a, lda, x, incx, beta, y, incy)
DGBMV
Definition dgbmv.f:188
logical function disnan(din)
DISNAN tests input for NaN.
Definition disnan.f:59
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: