LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zgtt02.f
Go to the documentation of this file.
1 *> \brief \b ZGTT02
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 ZGTT02( TRANS, N, NRHS, DL, D, DU, X, LDX, B, LDB,
12 * RESID )
13 *
14 * .. Scalar Arguments ..
15 * CHARACTER TRANS
16 * INTEGER LDB, LDX, N, NRHS
17 * DOUBLE PRECISION RESID
18 * ..
19 * .. Array Arguments ..
20 * COMPLEX*16 B( LDB, * ), D( * ), DL( * ), DU( * ),
21 * $ X( LDX, * )
22 * ..
23 *
24 *
25 *> \par Purpose:
26 * =============
27 *>
28 *> \verbatim
29 *>
30 *> ZGTT02 computes the residual for the solution to a tridiagonal
31 *> system of equations:
32 *> RESID = norm(B - op(A)*X) / (norm(A) * norm(X) * EPS),
33 *> where EPS is the machine epsilon.
34 *> \endverbatim
35 *
36 * Arguments:
37 * ==========
38 *
39 *> \param[in] TRANS
40 *> \verbatim
41 *> TRANS is CHARACTER
42 *> Specifies the form of the residual.
43 *> = 'N': B - A * X (No transpose)
44 *> = 'T': B - A**T * X (Transpose)
45 *> = 'C': B - A**H * X (Conjugate transpose)
46 *> \endverbatim
47 *>
48 *> \param[in] N
49 *> \verbatim
50 *> N is INTEGTER
51 *> The order of the matrix A. N >= 0.
52 *> \endverbatim
53 *>
54 *> \param[in] NRHS
55 *> \verbatim
56 *> NRHS is INTEGER
57 *> The number of right hand sides, i.e., the number of columns
58 *> of the matrices B and X. NRHS >= 0.
59 *> \endverbatim
60 *>
61 *> \param[in] DL
62 *> \verbatim
63 *> DL is COMPLEX*16 array, dimension (N-1)
64 *> The (n-1) sub-diagonal elements of A.
65 *> \endverbatim
66 *>
67 *> \param[in] D
68 *> \verbatim
69 *> D is COMPLEX*16 array, dimension (N)
70 *> The diagonal elements of A.
71 *> \endverbatim
72 *>
73 *> \param[in] DU
74 *> \verbatim
75 *> DU is COMPLEX*16 array, dimension (N-1)
76 *> The (n-1) super-diagonal elements of A.
77 *> \endverbatim
78 *>
79 *> \param[in] X
80 *> \verbatim
81 *> X is COMPLEX*16 array, dimension (LDX,NRHS)
82 *> The computed solution vectors X.
83 *> \endverbatim
84 *>
85 *> \param[in] LDX
86 *> \verbatim
87 *> LDX is INTEGER
88 *> The leading dimension of the array X. LDX >= max(1,N).
89 *> \endverbatim
90 *>
91 *> \param[in,out] B
92 *> \verbatim
93 *> B is COMPLEX*16 array, dimension (LDB,NRHS)
94 *> On entry, the right hand side vectors for the system of
95 *> linear equations.
96 *> On exit, B is overwritten with the difference B - op(A)*X.
97 *> \endverbatim
98 *>
99 *> \param[in] LDB
100 *> \verbatim
101 *> LDB is INTEGER
102 *> The leading dimension of the array B. LDB >= max(1,N).
103 *> \endverbatim
104 *>
105 *> \param[out] RESID
106 *> \verbatim
107 *> RESID is DOUBLE PRECISION
108 *> norm(B - op(A)*X) / (norm(A) * norm(X) * EPS)
109 *> \endverbatim
110 *
111 * Authors:
112 * ========
113 *
114 *> \author Univ. of Tennessee
115 *> \author Univ. of California Berkeley
116 *> \author Univ. of Colorado Denver
117 *> \author NAG Ltd.
118 *
119 *> \date November 2011
120 *
121 *> \ingroup complex16_lin
122 *
123 * =====================================================================
124  SUBROUTINE zgtt02( TRANS, N, NRHS, DL, D, DU, X, LDX, B, LDB,
125  $ resid )
126 *
127 * -- LAPACK test routine (version 3.4.0) --
128 * -- LAPACK is a software package provided by Univ. of Tennessee, --
129 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
130 * November 2011
131 *
132 * .. Scalar Arguments ..
133  CHARACTER trans
134  INTEGER ldb, ldx, n, nrhs
135  DOUBLE PRECISION resid
136 * ..
137 * .. Array Arguments ..
138  COMPLEX*16 b( ldb, * ), d( * ), dl( * ), du( * ),
139  $ x( ldx, * )
140 * ..
141 *
142 * =====================================================================
143 *
144 * .. Parameters ..
145  DOUBLE PRECISION one, zero
146  parameter( one = 1.0d+0, zero = 0.0d+0 )
147 * ..
148 * .. Local Scalars ..
149  INTEGER j
150  DOUBLE PRECISION anorm, bnorm, eps, xnorm
151 * ..
152 * .. External Functions ..
153  LOGICAL lsame
154  DOUBLE PRECISION dlamch, dzasum, zlangt
155  EXTERNAL lsame, dlamch, dzasum, zlangt
156 * ..
157 * .. External Subroutines ..
158  EXTERNAL zlagtm
159 * ..
160 * .. Intrinsic Functions ..
161  INTRINSIC max
162 * ..
163 * .. Executable Statements ..
164 *
165 * Quick exit if N = 0 or NRHS = 0
166 *
167  resid = zero
168  IF( n.LE.0 .OR. nrhs.EQ.0 )
169  $ return
170 *
171 * Compute the maximum over the number of right hand sides of
172 * norm(B - op(A)*X) / ( norm(A) * norm(X) * EPS ).
173 *
174  IF( lsame( trans, 'N' ) ) THEN
175  anorm = zlangt( '1', n, dl, d, du )
176  ELSE
177  anorm = zlangt( 'I', n, dl, d, du )
178  END IF
179 *
180 * Exit with RESID = 1/EPS if ANORM = 0.
181 *
182  eps = dlamch( 'Epsilon' )
183  IF( anorm.LE.zero ) THEN
184  resid = one / eps
185  return
186  END IF
187 *
188 * Compute B - op(A)*X.
189 *
190  CALL zlagtm( trans, n, nrhs, -one, dl, d, du, x, ldx, one, b,
191  $ ldb )
192 *
193  DO 10 j = 1, nrhs
194  bnorm = dzasum( n, b( 1, j ), 1 )
195  xnorm = dzasum( n, x( 1, j ), 1 )
196  IF( xnorm.LE.zero ) THEN
197  resid = one / eps
198  ELSE
199  resid = max( resid, ( ( bnorm / anorm ) / xnorm ) / eps )
200  END IF
201  10 continue
202 *
203  return
204 *
205 * End of ZGTT02
206 *
207  END