LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
dtbt03.f
Go to the documentation of this file.
1 *> \brief \b DTBT03
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE DTBT03( UPLO, TRANS, DIAG, N, KD, NRHS, AB, LDAB,
12 * SCALE, CNORM, TSCAL, X, LDX, B, LDB, WORK,
13 * RESID )
14 *
15 * .. Scalar Arguments ..
16 * CHARACTER DIAG, TRANS, UPLO
17 * INTEGER KD, LDAB, LDB, LDX, N, NRHS
18 * DOUBLE PRECISION RESID, SCALE, TSCAL
19 * ..
20 * .. Array Arguments ..
21 * DOUBLE PRECISION AB( LDAB, * ), B( LDB, * ), CNORM( * ),
22 * $ WORK( * ), X( LDX, * )
23 * ..
24 *
25 *
26 *> \par Purpose:
27 * =============
28 *>
29 *> \verbatim
30 *>
31 *> DTBT03 computes the residual for the solution to a scaled triangular
32 *> system of equations A*x = s*b or A'*x = s*b when A is a
33 *> triangular band matrix. Here A' is the transpose of A, s is a scalar,
34 *> and x and b are N by NRHS matrices. The test ratio is the maximum
35 *> over the number of right hand sides of
36 *> norm(s*b - op(A)*x) / ( norm(op(A)) * norm(x) * EPS ),
37 *> where op(A) denotes A or A' and EPS is the machine epsilon.
38 *> \endverbatim
39 *
40 * Arguments:
41 * ==========
42 *
43 *> \param[in] UPLO
44 *> \verbatim
45 *> UPLO is CHARACTER*1
46 *> Specifies whether the matrix A is upper or lower triangular.
47 *> = 'U': Upper triangular
48 *> = 'L': Lower triangular
49 *> \endverbatim
50 *>
51 *> \param[in] TRANS
52 *> \verbatim
53 *> TRANS is CHARACTER*1
54 *> Specifies the operation applied to A.
55 *> = 'N': A *x = b (No transpose)
56 *> = 'T': A'*x = b (Transpose)
57 *> = 'C': A'*x = b (Conjugate transpose = Transpose)
58 *> \endverbatim
59 *>
60 *> \param[in] DIAG
61 *> \verbatim
62 *> DIAG is CHARACTER*1
63 *> Specifies whether or not the matrix A is unit triangular.
64 *> = 'N': Non-unit triangular
65 *> = 'U': Unit triangular
66 *> \endverbatim
67 *>
68 *> \param[in] N
69 *> \verbatim
70 *> N is INTEGER
71 *> The order of the matrix A. N >= 0.
72 *> \endverbatim
73 *>
74 *> \param[in] KD
75 *> \verbatim
76 *> KD is INTEGER
77 *> The number of superdiagonals or subdiagonals of the
78 *> triangular band matrix A. KD >= 0.
79 *> \endverbatim
80 *>
81 *> \param[in] NRHS
82 *> \verbatim
83 *> NRHS is INTEGER
84 *> The number of right hand sides, i.e., the number of columns
85 *> of the matrices X and B. NRHS >= 0.
86 *> \endverbatim
87 *>
88 *> \param[in] AB
89 *> \verbatim
90 *> AB is DOUBLE PRECISION array, dimension (LDAB,N)
91 *> The upper or lower triangular band matrix A, stored in the
92 *> first kd+1 rows of the array. The j-th column of A is stored
93 *> in the j-th column of the array AB as follows:
94 *> if UPLO = 'U', AB(kd+1+i-j,j) = A(i,j) for max(1,j-kd)<=i<=j;
95 *> if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(n,j+kd).
96 *> \endverbatim
97 *>
98 *> \param[in] LDAB
99 *> \verbatim
100 *> LDAB is INTEGER
101 *> The leading dimension of the array AB. LDAB >= KD+1.
102 *> \endverbatim
103 *>
104 *> \param[in] SCALE
105 *> \verbatim
106 *> SCALE is DOUBLE PRECISION
107 *> The scaling factor s used in solving the triangular system.
108 *> \endverbatim
109 *>
110 *> \param[in] CNORM
111 *> \verbatim
112 *> CNORM is DOUBLE PRECISION array, dimension (N)
113 *> The 1-norms of the columns of A, not counting the diagonal.
114 *> \endverbatim
115 *>
116 *> \param[in] TSCAL
117 *> \verbatim
118 *> TSCAL is DOUBLE PRECISION
119 *> The scaling factor used in computing the 1-norms in CNORM.
120 *> CNORM actually contains the column norms of TSCAL*A.
121 *> \endverbatim
122 *>
123 *> \param[in] X
124 *> \verbatim
125 *> X is DOUBLE PRECISION array, dimension (LDX,NRHS)
126 *> The computed solution vectors for the system of linear
127 *> equations.
128 *> \endverbatim
129 *>
130 *> \param[in] LDX
131 *> \verbatim
132 *> LDX is INTEGER
133 *> The leading dimension of the array X. LDX >= max(1,N).
134 *> \endverbatim
135 *>
136 *> \param[in] B
137 *> \verbatim
138 *> B is DOUBLE PRECISION array, dimension (LDB,NRHS)
139 *> The right hand side vectors for the system of linear
140 *> equations.
141 *> \endverbatim
142 *>
143 *> \param[in] LDB
144 *> \verbatim
145 *> LDB is INTEGER
146 *> The leading dimension of the array B. LDB >= max(1,N).
147 *> \endverbatim
148 *>
149 *> \param[out] WORK
150 *> \verbatim
151 *> WORK is DOUBLE PRECISION array, dimension (N)
152 *> \endverbatim
153 *>
154 *> \param[out] RESID
155 *> \verbatim
156 *> RESID is DOUBLE PRECISION
157 *> The maximum over the number of right hand sides of
158 *> norm(op(A)*x - s*b) / ( norm(op(A)) * norm(x) * EPS ).
159 *> \endverbatim
160 *
161 * Authors:
162 * ========
163 *
164 *> \author Univ. of Tennessee
165 *> \author Univ. of California Berkeley
166 *> \author Univ. of Colorado Denver
167 *> \author NAG Ltd.
168 *
169 *> \date November 2011
170 *
171 *> \ingroup double_lin
172 *
173 * =====================================================================
174  SUBROUTINE dtbt03( UPLO, TRANS, DIAG, N, KD, NRHS, AB, LDAB,
175  $ scale, cnorm, tscal, x, ldx, b, ldb, work,
176  $ resid )
177 *
178 * -- LAPACK test routine (version 3.4.0) --
179 * -- LAPACK is a software package provided by Univ. of Tennessee, --
180 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
181 * November 2011
182 *
183 * .. Scalar Arguments ..
184  CHARACTER diag, trans, uplo
185  INTEGER kd, ldab, ldb, ldx, n, nrhs
186  DOUBLE PRECISION resid, scale, tscal
187 * ..
188 * .. Array Arguments ..
189  DOUBLE PRECISION ab( ldab, * ), b( ldb, * ), cnorm( * ),
190  $ work( * ), x( ldx, * )
191 * ..
192 *
193 * =====================================================================
194 *
195 * .. Parameters ..
196  DOUBLE PRECISION one, zero
197  parameter( one = 1.0d+0, zero = 0.0d+0 )
198 * ..
199 * .. Local Scalars ..
200  INTEGER ix, j
201  DOUBLE PRECISION bignum, eps, err, smlnum, tnorm, xnorm, xscal
202 * ..
203 * .. External Functions ..
204  LOGICAL lsame
205  INTEGER idamax
206  DOUBLE PRECISION dlamch
207  EXTERNAL lsame, idamax, dlamch
208 * ..
209 * .. External Subroutines ..
210  EXTERNAL daxpy, dcopy, dlabad, dscal, dtbmv
211 * ..
212 * .. Intrinsic Functions ..
213  INTRINSIC abs, dble, max
214 * ..
215 * .. Executable Statements ..
216 *
217 * Quick exit if N = 0
218 *
219  IF( n.LE.0 .OR. nrhs.LE.0 ) THEN
220  resid = zero
221  return
222  END IF
223  eps = dlamch( 'Epsilon' )
224  smlnum = dlamch( 'Safe minimum' )
225  bignum = one / smlnum
226  CALL dlabad( smlnum, bignum )
227 *
228 * Compute the norm of the triangular matrix A using the column
229 * norms already computed by DLATBS.
230 *
231  tnorm = zero
232  IF( lsame( diag, 'N' ) ) THEN
233  IF( lsame( uplo, 'U' ) ) THEN
234  DO 10 j = 1, n
235  tnorm = max( tnorm, tscal*abs( ab( kd+1, j ) )+
236  $ cnorm( j ) )
237  10 continue
238  ELSE
239  DO 20 j = 1, n
240  tnorm = max( tnorm, tscal*abs( ab( 1, j ) )+cnorm( j ) )
241  20 continue
242  END IF
243  ELSE
244  DO 30 j = 1, n
245  tnorm = max( tnorm, tscal+cnorm( j ) )
246  30 continue
247  END IF
248 *
249 * Compute the maximum over the number of right hand sides of
250 * norm(op(A)*x - s*b) / ( norm(op(A)) * norm(x) * EPS ).
251 *
252  resid = zero
253  DO 40 j = 1, nrhs
254  CALL dcopy( n, x( 1, j ), 1, work, 1 )
255  ix = idamax( n, work, 1 )
256  xnorm = max( one, abs( x( ix, j ) ) )
257  xscal = ( one / xnorm ) / dble( kd+1 )
258  CALL dscal( n, xscal, work, 1 )
259  CALL dtbmv( uplo, trans, diag, n, kd, ab, ldab, work, 1 )
260  CALL daxpy( n, -scale*xscal, b( 1, j ), 1, work, 1 )
261  ix = idamax( n, work, 1 )
262  err = tscal*abs( work( ix ) )
263  ix = idamax( n, x( 1, j ), 1 )
264  xnorm = abs( x( ix, j ) )
265  IF( err*smlnum.LE.xnorm ) THEN
266  IF( xnorm.GT.zero )
267  $ err = err / xnorm
268  ELSE
269  IF( err.GT.zero )
270  $ err = one / eps
271  END IF
272  IF( err*smlnum.LE.tnorm ) THEN
273  IF( tnorm.GT.zero )
274  $ err = err / tnorm
275  ELSE
276  IF( err.GT.zero )
277  $ err = one / eps
278  END IF
279  resid = max( resid, err )
280  40 continue
281 *
282  return
283 *
284 * End of DTBT03
285 *
286  END