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