LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
strt03.f
Go to the documentation of this file.
1 *> \brief \b STRT03
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 STRT03( 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 * REAL RESID, SCALE, TSCAL
18 * ..
19 * .. Array Arguments ..
20 * REAL A( LDA, * ), B( LDB, * ), CNORM( * ),
21 * $ WORK( * ), X( LDX, * )
22 * ..
23 *
24 *
25 *> \par Purpose:
26 * =============
27 *>
28 *> \verbatim
29 *>
30 *> STRT03 computes the residual for the solution to a scaled triangular
31 *> system of equations A*x = s*b or A'*x = s*b.
32 *> Here A is a triangular matrix, A' is the transpose of A, s is a
33 *> scalar, and x and b are N by NRHS matrices. The test ratio is the
34 *> maximum over the number of right hand sides of
35 *> norm(s*b - op(A)*x) / ( norm(op(A)) * norm(x) * EPS ),
36 *> where op(A) denotes A or A' 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 = s*b (No transpose)
55 *> = 'T': A'*x = s*b (Transpose)
56 *> = 'C': A'*x = s*b (Conjugate transpose = 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 REAL 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] SCALE
100 *> \verbatim
101 *> SCALE is REAL
102 *> The scaling factor s used in solving the triangular system.
103 *> \endverbatim
104 *>
105 *> \param[in] CNORM
106 *> \verbatim
107 *> CNORM is REAL array, dimension (N)
108 *> The 1-norms of the columns of A, not counting the diagonal.
109 *> \endverbatim
110 *>
111 *> \param[in] TSCAL
112 *> \verbatim
113 *> TSCAL is REAL
114 *> The scaling factor used in computing the 1-norms in CNORM.
115 *> CNORM actually contains the column norms of TSCAL*A.
116 *> \endverbatim
117 *>
118 *> \param[in] X
119 *> \verbatim
120 *> X is REAL array, dimension (LDX,NRHS)
121 *> The computed solution vectors for the system of linear
122 *> equations.
123 *> \endverbatim
124 *>
125 *> \param[in] LDX
126 *> \verbatim
127 *> LDX is INTEGER
128 *> The leading dimension of the array X. LDX >= max(1,N).
129 *> \endverbatim
130 *>
131 *> \param[in] B
132 *> \verbatim
133 *> B is REAL array, dimension (LDB,NRHS)
134 *> The right hand side vectors for the system of linear
135 *> equations.
136 *> \endverbatim
137 *>
138 *> \param[in] LDB
139 *> \verbatim
140 *> LDB is INTEGER
141 *> The leading dimension of the array B. LDB >= max(1,N).
142 *> \endverbatim
143 *>
144 *> \param[out] WORK
145 *> \verbatim
146 *> WORK is REAL array, dimension (N)
147 *> \endverbatim
148 *>
149 *> \param[out] RESID
150 *> \verbatim
151 *> RESID is REAL
152 *> The maximum over the number of right hand sides of
153 *> norm(op(A)*x - s*b) / ( norm(op(A)) * norm(x) * EPS ).
154 *> \endverbatim
155 *
156 * Authors:
157 * ========
158 *
159 *> \author Univ. of Tennessee
160 *> \author Univ. of California Berkeley
161 *> \author Univ. of Colorado Denver
162 *> \author NAG Ltd.
163 *
164 *> \date November 2011
165 *
166 *> \ingroup single_lin
167 *
168 * =====================================================================
169  SUBROUTINE strt03( UPLO, TRANS, DIAG, N, NRHS, A, LDA, SCALE,
170  $ cnorm, tscal, x, ldx, b, ldb, work, resid )
171 *
172 * -- LAPACK test routine (version 3.4.0) --
173 * -- LAPACK is a software package provided by Univ. of Tennessee, --
174 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
175 * November 2011
176 *
177 * .. Scalar Arguments ..
178  CHARACTER DIAG, TRANS, UPLO
179  INTEGER LDA, LDB, LDX, N, NRHS
180  REAL RESID, SCALE, TSCAL
181 * ..
182 * .. Array Arguments ..
183  REAL A( lda, * ), B( ldb, * ), CNORM( * ),
184  $ work( * ), x( ldx, * )
185 * ..
186 *
187 * =====================================================================
188 *
189 * .. Parameters ..
190  REAL ONE, ZERO
191  parameter ( one = 1.0e+0, zero = 0.0e+0 )
192 * ..
193 * .. Local Scalars ..
194  INTEGER IX, J
195  REAL BIGNUM, EPS, ERR, SMLNUM, TNORM, XNORM, XSCAL
196 * ..
197 * .. External Functions ..
198  LOGICAL LSAME
199  INTEGER ISAMAX
200  REAL SLAMCH
201  EXTERNAL lsame, isamax, slamch
202 * ..
203 * .. External Subroutines ..
204  EXTERNAL saxpy, scopy, slabad, sscal, strmv
205 * ..
206 * .. Intrinsic Functions ..
207  INTRINSIC abs, max, real
208 * ..
209 * .. Executable Statements ..
210 *
211 * Quick exit if N = 0
212 *
213  IF( n.LE.0 .OR. nrhs.LE.0 ) THEN
214  resid = zero
215  RETURN
216  END IF
217  eps = slamch( 'Epsilon' )
218  smlnum = slamch( 'Safe minimum' )
219  bignum = one / smlnum
220  CALL slabad( smlnum, bignum )
221 *
222 * Compute the norm of the triangular matrix A using the column
223 * norms already computed by SLATRS.
224 *
225  tnorm = zero
226  IF( lsame( diag, 'N' ) ) THEN
227  DO 10 j = 1, n
228  tnorm = max( tnorm, tscal*abs( a( j, j ) )+cnorm( j ) )
229  10 CONTINUE
230  ELSE
231  DO 20 j = 1, n
232  tnorm = max( tnorm, tscal+cnorm( j ) )
233  20 CONTINUE
234  END IF
235 *
236 * Compute the maximum over the number of right hand sides of
237 * norm(op(A)*x - s*b) / ( norm(op(A)) * norm(x) * EPS ).
238 *
239  resid = zero
240  DO 30 j = 1, nrhs
241  CALL scopy( n, x( 1, j ), 1, work, 1 )
242  ix = isamax( n, work, 1 )
243  xnorm = max( one, abs( x( ix, j ) ) )
244  xscal = ( one / xnorm ) / REAL( n )
245  CALL sscal( n, xscal, work, 1 )
246  CALL strmv( uplo, trans, diag, n, a, lda, work, 1 )
247  CALL saxpy( n, -scale*xscal, b( 1, j ), 1, work, 1 )
248  ix = isamax( n, work, 1 )
249  err = tscal*abs( work( ix ) )
250  ix = isamax( n, x( 1, j ), 1 )
251  xnorm = abs( x( ix, j ) )
252  IF( err*smlnum.LE.xnorm ) THEN
253  IF( xnorm.GT.zero )
254  $ err = err / xnorm
255  ELSE
256  IF( err.GT.zero )
257  $ err = one / eps
258  END IF
259  IF( err*smlnum.LE.tnorm ) THEN
260  IF( tnorm.GT.zero )
261  $ err = err / tnorm
262  ELSE
263  IF( err.GT.zero )
264  $ err = one / eps
265  END IF
266  resid = max( resid, err )
267  30 CONTINUE
268 *
269  RETURN
270 *
271 * End of STRT03
272 *
273  END
subroutine slabad(SMALL, LARGE)
SLABAD
Definition: slabad.f:76
subroutine strt03(UPLO, TRANS, DIAG, N, NRHS, A, LDA, SCALE, CNORM, TSCAL, X, LDX, B, LDB, WORK, RESID)
STRT03
Definition: strt03.f:171
subroutine strmv(UPLO, TRANS, DIAG, N, A, LDA, X, INCX)
STRMV
Definition: strmv.f:149
subroutine saxpy(N, SA, SX, INCX, SY, INCY)
SAXPY
Definition: saxpy.f:54
subroutine sscal(N, SA, SX, INCX)
SSCAL
Definition: sscal.f:55
subroutine scopy(N, SX, INCX, SY, INCY)
SCOPY
Definition: scopy.f:53