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

◆ zgbt02()

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

ZGBT02

Purpose:
 ZGBT02 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, A**T, or A**H, depending on TRANS, and EPS is the
 machine epsilon.
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)
[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 COMPLEX*16 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 COMPLEX*16 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 COMPLEX*16 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 146 of file zgbt02.f.

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