LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
cgtt02.f
Go to the documentation of this file.
1*> \brief \b CGTT02
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 CGTT02( 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* REAL RESID
18* ..
19* .. Array Arguments ..
20* COMPLEX B( LDB, * ), D( * ), DL( * ), DU( * ),
21* $ X( LDX, * )
22* ..
23*
24*
25*> \par Purpose:
26* =============
27*>
28*> \verbatim
29*>
30*> CGTT02 computes the residual for the solution to a tridiagonal
31*> system of equations:
32*> RESID = norm(B - op(A)*X) / (norm(op(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 INTEGER
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 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 array, dimension (N)
70*> The diagonal elements of A.
71*> \endverbatim
72*>
73*> \param[in] DU
74*> \verbatim
75*> DU is COMPLEX 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 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 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 REAL
108*> norm(B - op(A)*X) / (norm(op(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*> \ingroup complex_lin
120*
121* =====================================================================
122 SUBROUTINE cgtt02( TRANS, N, NRHS, DL, D, DU, X, LDX, B, LDB,
123 $ RESID )
124*
125* -- LAPACK test routine --
126* -- LAPACK is a software package provided by Univ. of Tennessee, --
127* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
128*
129* .. Scalar Arguments ..
130 CHARACTER TRANS
131 INTEGER LDB, LDX, N, NRHS
132 REAL RESID
133* ..
134* .. Array Arguments ..
135 COMPLEX B( LDB, * ), D( * ), DL( * ), DU( * ),
136 $ x( ldx, * )
137* ..
138*
139* =====================================================================
140*
141* .. Parameters ..
142 REAL ONE, ZERO
143 parameter( one = 1.0e+0, zero = 0.0e+0 )
144* ..
145* .. Local Scalars ..
146 INTEGER J
147 REAL ANORM, BNORM, EPS, XNORM
148* ..
149* .. External Functions ..
150 LOGICAL LSAME
151 REAL CLANGT, SCASUM, SLAMCH
152 EXTERNAL lsame, clangt, scasum, slamch
153* ..
154* .. External Subroutines ..
155 EXTERNAL clagtm
156* ..
157* .. Intrinsic Functions ..
158 INTRINSIC max
159* ..
160* .. Executable Statements ..
161*
162* Quick exit if N = 0 or NRHS = 0
163*
164 resid = zero
165 IF( n.LE.0 .OR. nrhs.EQ.0 )
166 $ RETURN
167*
168* Compute the maximum over the number of right hand sides of
169* norm(B - op(A)*X) / ( norm(op(A)) * norm(X) * EPS ).
170*
171 IF( lsame( trans, 'N' ) ) THEN
172 anorm = clangt( '1', n, dl, d, du )
173 ELSE
174 anorm = clangt( 'I', n, dl, d, du )
175 END IF
176*
177* Exit with RESID = 1/EPS if ANORM = 0.
178*
179 eps = slamch( 'Epsilon' )
180 IF( anorm.LE.zero ) THEN
181 resid = one / eps
182 RETURN
183 END IF
184*
185* Compute B - op(A)*X and store in B.
186*
187 CALL clagtm( trans, n, nrhs, -one, dl, d, du, x, ldx, one, b,
188 $ ldb )
189*
190 DO 10 j = 1, nrhs
191 bnorm = scasum( n, b( 1, j ), 1 )
192 xnorm = scasum( n, x( 1, j ), 1 )
193 IF( xnorm.LE.zero ) THEN
194 resid = one / eps
195 ELSE
196 resid = max( resid, ( ( bnorm / anorm ) / xnorm ) / eps )
197 END IF
198 10 CONTINUE
199*
200 RETURN
201*
202* End of CGTT02
203*
204 END
subroutine cgtt02(trans, n, nrhs, dl, d, du, x, ldx, b, ldb, resid)
CGTT02
Definition cgtt02.f:124
subroutine clagtm(trans, n, nrhs, alpha, dl, d, du, x, ldx, beta, b, ldb)
CLAGTM performs a matrix-matrix product of the form C = αAB+βC, where A is a tridiagonal matrix,...
Definition clagtm.f:145