LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dptt02.f
Go to the documentation of this file.
1*> \brief \b DPTT02
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 DPTT02( N, NRHS, D, E, X, LDX, B, LDB, RESID )
12*
13* .. Scalar Arguments ..
14* INTEGER LDB, LDX, N, NRHS
15* DOUBLE PRECISION RESID
16* ..
17* .. Array Arguments ..
18* DOUBLE PRECISION B( LDB, * ), D( * ), E( * ), X( LDX, * )
19* ..
20*
21*
22*> \par Purpose:
23* =============
24*>
25*> \verbatim
26*>
27*> DPTT02 computes the residual for the solution to a symmetric
28*> tridiagonal system of equations:
29*> RESID = norm(B - A*X) / (norm(A) * norm(X) * EPS),
30*> where EPS is the machine epsilon.
31*> \endverbatim
32*
33* Arguments:
34* ==========
35*
36*> \param[in] N
37*> \verbatim
38*> N is INTEGER
39*> The order of the matrix A.
40*> \endverbatim
41*>
42*> \param[in] NRHS
43*> \verbatim
44*> NRHS is INTEGER
45*> The number of right hand sides, i.e., the number of columns
46*> of the matrices B and X. NRHS >= 0.
47*> \endverbatim
48*>
49*> \param[in] D
50*> \verbatim
51*> D is DOUBLE PRECISION array, dimension (N)
52*> The n diagonal elements of the tridiagonal matrix A.
53*> \endverbatim
54*>
55*> \param[in] E
56*> \verbatim
57*> E is DOUBLE PRECISION array, dimension (N-1)
58*> The (n-1) subdiagonal elements of the tridiagonal matrix A.
59*> \endverbatim
60*>
61*> \param[in] X
62*> \verbatim
63*> X is DOUBLE PRECISION array, dimension (LDX,NRHS)
64*> The n by nrhs matrix of solution vectors X.
65*> \endverbatim
66*>
67*> \param[in] LDX
68*> \verbatim
69*> LDX is INTEGER
70*> The leading dimension of the array X. LDX >= max(1,N).
71*> \endverbatim
72*>
73*> \param[in,out] B
74*> \verbatim
75*> B is DOUBLE PRECISION array, dimension (LDB,NRHS)
76*> On entry, the n by nrhs matrix of right hand side vectors B.
77*> On exit, B is overwritten with the difference B - A*X.
78*> \endverbatim
79*>
80*> \param[in] LDB
81*> \verbatim
82*> LDB is INTEGER
83*> The leading dimension of the array B. LDB >= max(1,N).
84*> \endverbatim
85*>
86*> \param[out] RESID
87*> \verbatim
88*> RESID is DOUBLE PRECISION
89*> norm(B - A*X) / (norm(A) * norm(X) * EPS)
90*> \endverbatim
91*
92* Authors:
93* ========
94*
95*> \author Univ. of Tennessee
96*> \author Univ. of California Berkeley
97*> \author Univ. of Colorado Denver
98*> \author NAG Ltd.
99*
100*> \ingroup double_lin
101*
102* =====================================================================
103 SUBROUTINE dptt02( N, NRHS, D, E, X, LDX, B, LDB, RESID )
104*
105* -- LAPACK test routine --
106* -- LAPACK is a software package provided by Univ. of Tennessee, --
107* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
108*
109* .. Scalar Arguments ..
110 INTEGER LDB, LDX, N, NRHS
111 DOUBLE PRECISION RESID
112* ..
113* .. Array Arguments ..
114 DOUBLE PRECISION B( LDB, * ), D( * ), E( * ), X( LDX, * )
115* ..
116*
117* =====================================================================
118*
119* .. Parameters ..
120 DOUBLE PRECISION ONE, ZERO
121 parameter( one = 1.0d+0, zero = 0.0d+0 )
122* ..
123* .. Local Scalars ..
124 INTEGER J
125 DOUBLE PRECISION ANORM, BNORM, EPS, XNORM
126* ..
127* .. External Functions ..
128 DOUBLE PRECISION DASUM, DLAMCH, DLANST
129 EXTERNAL dasum, dlamch, dlanst
130* ..
131* .. Intrinsic Functions ..
132 INTRINSIC max
133* ..
134* .. External Subroutines ..
135 EXTERNAL dlaptm
136* ..
137* .. Executable Statements ..
138*
139* Quick return if possible
140*
141 IF( n.LE.0 ) THEN
142 resid = zero
143 RETURN
144 END IF
145*
146* Compute the 1-norm of the tridiagonal matrix A.
147*
148 anorm = dlanst( '1', n, d, e )
149*
150* Exit with RESID = 1/EPS if ANORM = 0.
151*
152 eps = dlamch( 'Epsilon' )
153 IF( anorm.LE.zero ) THEN
154 resid = one / eps
155 RETURN
156 END IF
157*
158* Compute B - A*X.
159*
160 CALL dlaptm( n, nrhs, -one, d, e, x, ldx, one, b, ldb )
161*
162* Compute the maximum over the number of right hand sides of
163* norm(B - A*X) / ( norm(A) * norm(X) * EPS ).
164*
165 resid = zero
166 DO 10 j = 1, nrhs
167 bnorm = dasum( n, b( 1, j ), 1 )
168 xnorm = dasum( n, x( 1, j ), 1 )
169 IF( xnorm.LE.zero ) THEN
170 resid = one / eps
171 ELSE
172 resid = max( resid, ( ( bnorm / anorm ) / xnorm ) / eps )
173 END IF
174 10 CONTINUE
175*
176 RETURN
177*
178* End of DPTT02
179*
180 END
subroutine dlaptm(n, nrhs, alpha, d, e, x, ldx, beta, b, ldb)
DLAPTM
Definition dlaptm.f:116
subroutine dptt02(n, nrhs, d, e, x, ldx, b, ldb, resid)
DPTT02
Definition dptt02.f:104