LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
ztrt02.f
Go to the documentation of this file.
1*> \brief \b ZTRT02
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 ZTRT02( UPLO, TRANS, DIAG, N, NRHS, A, LDA, X, LDX, B,
12* LDB, WORK, RWORK, RESID )
13*
14* .. Scalar Arguments ..
15* CHARACTER DIAG, TRANS, UPLO
16* INTEGER LDA, LDB, LDX, N, NRHS
17* DOUBLE PRECISION RESID
18* ..
19* .. Array Arguments ..
20* DOUBLE PRECISION RWORK( * )
21* COMPLEX*16 A( LDA, * ), B( LDB, * ), WORK( * ),
22* $ X( LDX, * )
23* ..
24*
25*
26*> \par Purpose:
27* =============
28*>
29*> \verbatim
30*>
31*> ZTRT02 computes the residual for the computed solution to a
32*> triangular system of linear equations op(A)*X = B, where A is a
33*> triangular matrix. The test ratio is the maximum over
34*> norm(b - op(A)*x) / ( ||op(A)||_1 * norm(x) * EPS ),
35*> where op(A) = A, A**T, or A**H, b is the column of B, x is the
36*> solution vector, and EPS is the machine epsilon.
37*> \endverbatim
38*
39* Arguments:
40* ==========
41*
42*> \param[in] UPLO
43*> \verbatim
44*> UPLO is CHARACTER*1
45*> Specifies whether the matrix A is upper or lower triangular.
46*> = 'U': Upper triangular
47*> = 'L': Lower triangular
48*> \endverbatim
49*>
50*> \param[in] TRANS
51*> \verbatim
52*> TRANS is CHARACTER*1
53*> Specifies the operation applied to A.
54*> = 'N': A * X = B (No transpose)
55*> = 'T': A**T * X = B (Transpose)
56*> = 'C': A**H * X = B (Conjugate transpose)
57*> \endverbatim
58*>
59*> \param[in] DIAG
60*> \verbatim
61*> DIAG is CHARACTER*1
62*> Specifies whether or not the matrix A is unit triangular.
63*> = 'N': Non-unit triangular
64*> = 'U': Unit triangular
65*> \endverbatim
66*>
67*> \param[in] N
68*> \verbatim
69*> N is INTEGER
70*> The order of the matrix A. N >= 0.
71*> \endverbatim
72*>
73*> \param[in] NRHS
74*> \verbatim
75*> NRHS is INTEGER
76*> The number of right hand sides, i.e., the number of columns
77*> of the matrices X and B. NRHS >= 0.
78*> \endverbatim
79*>
80*> \param[in] A
81*> \verbatim
82*> A is COMPLEX*16 array, dimension (LDA,N)
83*> The triangular matrix A. If UPLO = 'U', the leading n by n
84*> upper triangular part of the array A contains the upper
85*> triangular matrix, and the strictly lower triangular part of
86*> A is not referenced. If UPLO = 'L', the leading n by n lower
87*> triangular part of the array A contains the lower triangular
88*> matrix, and the strictly upper triangular part of A is not
89*> referenced. If DIAG = 'U', the diagonal elements of A are
90*> also not referenced and are assumed to be 1.
91*> \endverbatim
92*>
93*> \param[in] LDA
94*> \verbatim
95*> LDA is INTEGER
96*> The leading dimension of the array A. LDA >= max(1,N).
97*> \endverbatim
98*>
99*> \param[in] X
100*> \verbatim
101*> X is COMPLEX*16 array, dimension (LDX,NRHS)
102*> The computed solution vectors for the system of linear
103*> equations.
104*> \endverbatim
105*>
106*> \param[in] LDX
107*> \verbatim
108*> LDX is INTEGER
109*> The leading dimension of the array X. LDX >= max(1,N).
110*> \endverbatim
111*>
112*> \param[in] B
113*> \verbatim
114*> B is COMPLEX*16 array, dimension (LDB,NRHS)
115*> The right hand side vectors for the system of linear
116*> equations.
117*> \endverbatim
118*>
119*> \param[in] LDB
120*> \verbatim
121*> LDB is INTEGER
122*> The leading dimension of the array B. LDB >= max(1,N).
123*> \endverbatim
124*>
125*> \param[out] WORK
126*> \verbatim
127*> WORK is COMPLEX*16 array, dimension (N)
128*> \endverbatim
129*>
130*> \param[out] RWORK
131*> \verbatim
132*> RWORK is DOUBLE PRECISION array, dimension (N)
133*> \endverbatim
134*>
135*> \param[out] RESID
136*> \verbatim
137*> RESID is DOUBLE PRECISION
138*> The maximum over the number of right hand sides of
139*> norm(op(A)*X - B) / ( norm(op(A)) * norm(X) * EPS ).
140*> \endverbatim
141*
142* Authors:
143* ========
144*
145*> \author Univ. of Tennessee
146*> \author Univ. of California Berkeley
147*> \author Univ. of Colorado Denver
148*> \author NAG Ltd.
149*
150*> \ingroup complex16_lin
151*
152* =====================================================================
153 SUBROUTINE ztrt02( UPLO, TRANS, DIAG, N, NRHS, A, LDA, X, LDX, B,
154 $ LDB, WORK, RWORK, RESID )
155*
156* -- LAPACK test routine --
157* -- LAPACK is a software package provided by Univ. of Tennessee, --
158* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
159*
160* .. Scalar Arguments ..
161 CHARACTER DIAG, TRANS, UPLO
162 INTEGER LDA, LDB, LDX, N, NRHS
163 DOUBLE PRECISION RESID
164* ..
165* .. Array Arguments ..
166 DOUBLE PRECISION RWORK( * )
167 COMPLEX*16 A( LDA, * ), B( LDB, * ), WORK( * ),
168 $ x( ldx, * )
169* ..
170*
171* =====================================================================
172*
173* .. Parameters ..
174 DOUBLE PRECISION ZERO, ONE
175 parameter( zero = 0.0d+0, one = 1.0d+0 )
176* ..
177* .. Local Scalars ..
178 INTEGER J
179 DOUBLE PRECISION ANORM, BNORM, EPS, XNORM
180* ..
181* .. External Functions ..
182 LOGICAL LSAME
183 DOUBLE PRECISION DLAMCH, DZASUM, ZLANTR
184 EXTERNAL lsame, dlamch, dzasum, zlantr
185* ..
186* .. External Subroutines ..
187 EXTERNAL zaxpy, zcopy, ztrmv
188* ..
189* .. Intrinsic Functions ..
190 INTRINSIC dcmplx, max
191* ..
192* .. Executable Statements ..
193*
194* Quick exit if N = 0 or NRHS = 0
195*
196 IF( n.LE.0 .OR. nrhs.LE.0 ) THEN
197 resid = zero
198 RETURN
199 END IF
200*
201* Compute the 1-norm of op(A).
202*
203 IF( lsame( trans, 'N' ) ) THEN
204 anorm = zlantr( '1', uplo, diag, n, n, a, lda, rwork )
205 ELSE
206 anorm = zlantr( 'I', uplo, diag, n, n, a, lda, rwork )
207 END IF
208*
209* Exit with RESID = 1/EPS if ANORM = 0.
210*
211 eps = dlamch( 'Epsilon' )
212 IF( anorm.LE.zero ) THEN
213 resid = one / eps
214 RETURN
215 END IF
216*
217* Compute the maximum over the number of right hand sides of
218* norm(op(A)*X - B) / ( norm(op(A)) * norm(X) * EPS )
219*
220 resid = zero
221 DO 10 j = 1, nrhs
222 CALL zcopy( n, x( 1, j ), 1, work, 1 )
223 CALL ztrmv( uplo, trans, diag, n, a, lda, work, 1 )
224 CALL zaxpy( n, dcmplx( -one ), b( 1, j ), 1, work, 1 )
225 bnorm = dzasum( n, work, 1 )
226 xnorm = dzasum( n, x( 1, j ), 1 )
227 IF( xnorm.LE.zero ) THEN
228 resid = one / eps
229 ELSE
230 resid = max( resid, ( ( bnorm / anorm ) / xnorm ) / eps )
231 END IF
232 10 CONTINUE
233*
234 RETURN
235*
236* End of ZTRT02
237*
238 END
subroutine zaxpy(n, za, zx, incx, zy, incy)
ZAXPY
Definition zaxpy.f:88
subroutine zcopy(n, zx, incx, zy, incy)
ZCOPY
Definition zcopy.f:81
subroutine ztrmv(uplo, trans, diag, n, a, lda, x, incx)
ZTRMV
Definition ztrmv.f:147
subroutine ztrt02(uplo, trans, diag, n, nrhs, a, lda, x, ldx, b, ldb, work, rwork, resid)
ZTRT02
Definition ztrt02.f:155