LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
dtrrfs.f
Go to the documentation of this file.
1 *> \brief \b DTRRFS
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download DTRRFS + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dtrrfs.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dtrrfs.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dtrrfs.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE DTRRFS( UPLO, TRANS, DIAG, N, NRHS, A, LDA, B, LDB, X,
22 * LDX, FERR, BERR, WORK, IWORK, INFO )
23 *
24 * .. Scalar Arguments ..
25 * CHARACTER DIAG, TRANS, UPLO
26 * INTEGER INFO, LDA, LDB, LDX, N, NRHS
27 * ..
28 * .. Array Arguments ..
29 * INTEGER IWORK( * )
30 * DOUBLE PRECISION A( LDA, * ), B( LDB, * ), BERR( * ), FERR( * ),
31 * $ WORK( * ), X( LDX, * )
32 * ..
33 *
34 *
35 *> \par Purpose:
36 * =============
37 *>
38 *> \verbatim
39 *>
40 *> DTRRFS provides error bounds and backward error estimates for the
41 *> solution to a system of linear equations with a triangular
42 *> coefficient matrix.
43 *>
44 *> The solution matrix X must be computed by DTRTRS or some other
45 *> means before entering this routine. DTRRFS does not do iterative
46 *> refinement because doing so cannot improve the backward error.
47 *> \endverbatim
48 *
49 * Arguments:
50 * ==========
51 *
52 *> \param[in] UPLO
53 *> \verbatim
54 *> UPLO is CHARACTER*1
55 *> = 'U': A is upper triangular;
56 *> = 'L': A is lower triangular.
57 *> \endverbatim
58 *>
59 *> \param[in] TRANS
60 *> \verbatim
61 *> TRANS is CHARACTER*1
62 *> Specifies the form of the system of equations:
63 *> = 'N': A * X = B (No transpose)
64 *> = 'T': A**T * X = B (Transpose)
65 *> = 'C': A**H * X = B (Conjugate transpose = Transpose)
66 *> \endverbatim
67 *>
68 *> \param[in] DIAG
69 *> \verbatim
70 *> DIAG is CHARACTER*1
71 *> = 'N': A is non-unit triangular;
72 *> = 'U': A is unit triangular.
73 *> \endverbatim
74 *>
75 *> \param[in] N
76 *> \verbatim
77 *> N is INTEGER
78 *> The order of the matrix A. N >= 0.
79 *> \endverbatim
80 *>
81 *> \param[in] NRHS
82 *> \verbatim
83 *> NRHS is INTEGER
84 *> The number of right hand sides, i.e., the number of columns
85 *> of the matrices B and X. NRHS >= 0.
86 *> \endverbatim
87 *>
88 *> \param[in] A
89 *> \verbatim
90 *> A is DOUBLE PRECISION array, dimension (LDA,N)
91 *> The triangular matrix A. If UPLO = 'U', the leading N-by-N
92 *> upper triangular part of the array A contains the upper
93 *> triangular matrix, and the strictly lower triangular part of
94 *> A is not referenced. If UPLO = 'L', the leading N-by-N lower
95 *> triangular part of the array A contains the lower triangular
96 *> matrix, and the strictly upper triangular part of A is not
97 *> referenced. If DIAG = 'U', the diagonal elements of A are
98 *> also not referenced and are assumed to be 1.
99 *> \endverbatim
100 *>
101 *> \param[in] LDA
102 *> \verbatim
103 *> LDA is INTEGER
104 *> The leading dimension of the array A. LDA >= max(1,N).
105 *> \endverbatim
106 *>
107 *> \param[in] B
108 *> \verbatim
109 *> B is DOUBLE PRECISION array, dimension (LDB,NRHS)
110 *> The right hand side matrix B.
111 *> \endverbatim
112 *>
113 *> \param[in] LDB
114 *> \verbatim
115 *> LDB is INTEGER
116 *> The leading dimension of the array B. LDB >= max(1,N).
117 *> \endverbatim
118 *>
119 *> \param[in] X
120 *> \verbatim
121 *> X is DOUBLE PRECISION array, dimension (LDX,NRHS)
122 *> The solution matrix X.
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[out] FERR
132 *> \verbatim
133 *> FERR is DOUBLE PRECISION array, dimension (NRHS)
134 *> The estimated forward error bound for each solution vector
135 *> X(j) (the j-th column of the solution matrix X).
136 *> If XTRUE is the true solution corresponding to X(j), FERR(j)
137 *> is an estimated upper bound for the magnitude of the largest
138 *> element in (X(j) - XTRUE) divided by the magnitude of the
139 *> largest element in X(j). The estimate is as reliable as
140 *> the estimate for RCOND, and is almost always a slight
141 *> overestimate of the true error.
142 *> \endverbatim
143 *>
144 *> \param[out] BERR
145 *> \verbatim
146 *> BERR is DOUBLE PRECISION array, dimension (NRHS)
147 *> The componentwise relative backward error of each solution
148 *> vector X(j) (i.e., the smallest relative change in
149 *> any element of A or B that makes X(j) an exact solution).
150 *> \endverbatim
151 *>
152 *> \param[out] WORK
153 *> \verbatim
154 *> WORK is DOUBLE PRECISION array, dimension (3*N)
155 *> \endverbatim
156 *>
157 *> \param[out] IWORK
158 *> \verbatim
159 *> IWORK is INTEGER array, dimension (N)
160 *> \endverbatim
161 *>
162 *> \param[out] INFO
163 *> \verbatim
164 *> INFO is INTEGER
165 *> = 0: successful exit
166 *> < 0: if INFO = -i, the i-th argument had an illegal value
167 *> \endverbatim
168 *
169 * Authors:
170 * ========
171 *
172 *> \author Univ. of Tennessee
173 *> \author Univ. of California Berkeley
174 *> \author Univ. of Colorado Denver
175 *> \author NAG Ltd.
176 *
177 *> \date November 2011
178 *
179 *> \ingroup doubleOTHERcomputational
180 *
181 * =====================================================================
182  SUBROUTINE dtrrfs( UPLO, TRANS, DIAG, N, NRHS, A, LDA, B, LDB, X,
183  $ ldx, ferr, berr, work, iwork, info )
184 *
185 * -- LAPACK computational routine (version 3.4.0) --
186 * -- LAPACK is a software package provided by Univ. of Tennessee, --
187 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
188 * November 2011
189 *
190 * .. Scalar Arguments ..
191  CHARACTER diag, trans, uplo
192  INTEGER info, lda, ldb, ldx, n, nrhs
193 * ..
194 * .. Array Arguments ..
195  INTEGER iwork( * )
196  DOUBLE PRECISION a( lda, * ), b( ldb, * ), berr( * ), ferr( * ),
197  $ work( * ), x( ldx, * )
198 * ..
199 *
200 * =====================================================================
201 *
202 * .. Parameters ..
203  DOUBLE PRECISION zero
204  parameter( zero = 0.0d+0 )
205  DOUBLE PRECISION one
206  parameter( one = 1.0d+0 )
207 * ..
208 * .. Local Scalars ..
209  LOGICAL notran, nounit, upper
210  CHARACTER transt
211  INTEGER i, j, k, kase, nz
212  DOUBLE PRECISION eps, lstres, s, safe1, safe2, safmin, xk
213 * ..
214 * .. Local Arrays ..
215  INTEGER isave( 3 )
216 * ..
217 * .. External Subroutines ..
218  EXTERNAL daxpy, dcopy, dlacn2, dtrmv, dtrsv, xerbla
219 * ..
220 * .. Intrinsic Functions ..
221  INTRINSIC abs, max
222 * ..
223 * .. External Functions ..
224  LOGICAL lsame
225  DOUBLE PRECISION dlamch
226  EXTERNAL lsame, dlamch
227 * ..
228 * .. Executable Statements ..
229 *
230 * Test the input parameters.
231 *
232  info = 0
233  upper = lsame( uplo, 'U' )
234  notran = lsame( trans, 'N' )
235  nounit = lsame( diag, 'N' )
236 *
237  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
238  info = -1
239  ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'T' ) .AND. .NOT.
240  $ lsame( trans, 'C' ) ) THEN
241  info = -2
242  ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag, 'U' ) ) THEN
243  info = -3
244  ELSE IF( n.LT.0 ) THEN
245  info = -4
246  ELSE IF( nrhs.LT.0 ) THEN
247  info = -5
248  ELSE IF( lda.LT.max( 1, n ) ) THEN
249  info = -7
250  ELSE IF( ldb.LT.max( 1, n ) ) THEN
251  info = -9
252  ELSE IF( ldx.LT.max( 1, n ) ) THEN
253  info = -11
254  END IF
255  IF( info.NE.0 ) THEN
256  CALL xerbla( 'DTRRFS', -info )
257  return
258  END IF
259 *
260 * Quick return if possible
261 *
262  IF( n.EQ.0 .OR. nrhs.EQ.0 ) THEN
263  DO 10 j = 1, nrhs
264  ferr( j ) = zero
265  berr( j ) = zero
266  10 continue
267  return
268  END IF
269 *
270  IF( notran ) THEN
271  transt = 'T'
272  ELSE
273  transt = 'N'
274  END IF
275 *
276 * NZ = maximum number of nonzero elements in each row of A, plus 1
277 *
278  nz = n + 1
279  eps = dlamch( 'Epsilon' )
280  safmin = dlamch( 'Safe minimum' )
281  safe1 = nz*safmin
282  safe2 = safe1 / eps
283 *
284 * Do for each right hand side
285 *
286  DO 250 j = 1, nrhs
287 *
288 * Compute residual R = B - op(A) * X,
289 * where op(A) = A or A**T, depending on TRANS.
290 *
291  CALL dcopy( n, x( 1, j ), 1, work( n+1 ), 1 )
292  CALL dtrmv( uplo, trans, diag, n, a, lda, work( n+1 ), 1 )
293  CALL daxpy( n, -one, b( 1, j ), 1, work( n+1 ), 1 )
294 *
295 * Compute componentwise relative backward error from formula
296 *
297 * max(i) ( abs(R(i)) / ( abs(op(A))*abs(X) + abs(B) )(i) )
298 *
299 * where abs(Z) is the componentwise absolute value of the matrix
300 * or vector Z. If the i-th component of the denominator is less
301 * than SAFE2, then SAFE1 is added to the i-th components of the
302 * numerator and denominator before dividing.
303 *
304  DO 20 i = 1, n
305  work( i ) = abs( b( i, j ) )
306  20 continue
307 *
308  IF( notran ) THEN
309 *
310 * Compute abs(A)*abs(X) + abs(B).
311 *
312  IF( upper ) THEN
313  IF( nounit ) THEN
314  DO 40 k = 1, n
315  xk = abs( x( k, j ) )
316  DO 30 i = 1, k
317  work( i ) = work( i ) + abs( a( i, k ) )*xk
318  30 continue
319  40 continue
320  ELSE
321  DO 60 k = 1, n
322  xk = abs( x( k, j ) )
323  DO 50 i = 1, k - 1
324  work( i ) = work( i ) + abs( a( i, k ) )*xk
325  50 continue
326  work( k ) = work( k ) + xk
327  60 continue
328  END IF
329  ELSE
330  IF( nounit ) THEN
331  DO 80 k = 1, n
332  xk = abs( x( k, j ) )
333  DO 70 i = k, n
334  work( i ) = work( i ) + abs( a( i, k ) )*xk
335  70 continue
336  80 continue
337  ELSE
338  DO 100 k = 1, n
339  xk = abs( x( k, j ) )
340  DO 90 i = k + 1, n
341  work( i ) = work( i ) + abs( a( i, k ) )*xk
342  90 continue
343  work( k ) = work( k ) + xk
344  100 continue
345  END IF
346  END IF
347  ELSE
348 *
349 * Compute abs(A**T)*abs(X) + abs(B).
350 *
351  IF( upper ) THEN
352  IF( nounit ) THEN
353  DO 120 k = 1, n
354  s = zero
355  DO 110 i = 1, k
356  s = s + abs( a( i, k ) )*abs( x( i, j ) )
357  110 continue
358  work( k ) = work( k ) + s
359  120 continue
360  ELSE
361  DO 140 k = 1, n
362  s = abs( x( k, j ) )
363  DO 130 i = 1, k - 1
364  s = s + abs( a( i, k ) )*abs( x( i, j ) )
365  130 continue
366  work( k ) = work( k ) + s
367  140 continue
368  END IF
369  ELSE
370  IF( nounit ) THEN
371  DO 160 k = 1, n
372  s = zero
373  DO 150 i = k, n
374  s = s + abs( a( i, k ) )*abs( x( i, j ) )
375  150 continue
376  work( k ) = work( k ) + s
377  160 continue
378  ELSE
379  DO 180 k = 1, n
380  s = abs( x( k, j ) )
381  DO 170 i = k + 1, n
382  s = s + abs( a( i, k ) )*abs( x( i, j ) )
383  170 continue
384  work( k ) = work( k ) + s
385  180 continue
386  END IF
387  END IF
388  END IF
389  s = zero
390  DO 190 i = 1, n
391  IF( work( i ).GT.safe2 ) THEN
392  s = max( s, abs( work( n+i ) ) / work( i ) )
393  ELSE
394  s = max( s, ( abs( work( n+i ) )+safe1 ) /
395  $ ( work( i )+safe1 ) )
396  END IF
397  190 continue
398  berr( j ) = s
399 *
400 * Bound error from formula
401 *
402 * norm(X - XTRUE) / norm(X) .le. FERR =
403 * norm( abs(inv(op(A)))*
404 * ( abs(R) + NZ*EPS*( abs(op(A))*abs(X)+abs(B) ))) / norm(X)
405 *
406 * where
407 * norm(Z) is the magnitude of the largest component of Z
408 * inv(op(A)) is the inverse of op(A)
409 * abs(Z) is the componentwise absolute value of the matrix or
410 * vector Z
411 * NZ is the maximum number of nonzeros in any row of A, plus 1
412 * EPS is machine epsilon
413 *
414 * The i-th component of abs(R)+NZ*EPS*(abs(op(A))*abs(X)+abs(B))
415 * is incremented by SAFE1 if the i-th component of
416 * abs(op(A))*abs(X) + abs(B) is less than SAFE2.
417 *
418 * Use DLACN2 to estimate the infinity-norm of the matrix
419 * inv(op(A)) * diag(W),
420 * where W = abs(R) + NZ*EPS*( abs(op(A))*abs(X)+abs(B) )))
421 *
422  DO 200 i = 1, n
423  IF( work( i ).GT.safe2 ) THEN
424  work( i ) = abs( work( n+i ) ) + nz*eps*work( i )
425  ELSE
426  work( i ) = abs( work( n+i ) ) + nz*eps*work( i ) + safe1
427  END IF
428  200 continue
429 *
430  kase = 0
431  210 continue
432  CALL dlacn2( n, work( 2*n+1 ), work( n+1 ), iwork, ferr( j ),
433  $ kase, isave )
434  IF( kase.NE.0 ) THEN
435  IF( kase.EQ.1 ) THEN
436 *
437 * Multiply by diag(W)*inv(op(A)**T).
438 *
439  CALL dtrsv( uplo, transt, diag, n, a, lda, work( n+1 ),
440  $ 1 )
441  DO 220 i = 1, n
442  work( n+i ) = work( i )*work( n+i )
443  220 continue
444  ELSE
445 *
446 * Multiply by inv(op(A))*diag(W).
447 *
448  DO 230 i = 1, n
449  work( n+i ) = work( i )*work( n+i )
450  230 continue
451  CALL dtrsv( uplo, trans, diag, n, a, lda, work( n+1 ),
452  $ 1 )
453  END IF
454  go to 210
455  END IF
456 *
457 * Normalize error.
458 *
459  lstres = zero
460  DO 240 i = 1, n
461  lstres = max( lstres, abs( x( i, j ) ) )
462  240 continue
463  IF( lstres.NE.zero )
464  $ ferr( j ) = ferr( j ) / lstres
465 *
466  250 continue
467 *
468  return
469 *
470 * End of DTRRFS
471 *
472  END