LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
ztrt01.f
Go to the documentation of this file.
1 *> \brief \b ZTRT01
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 ZTRT01( UPLO, DIAG, N, A, LDA, AINV, LDAINV, RCOND,
12 * RWORK, RESID )
13 *
14 * .. Scalar Arguments ..
15 * CHARACTER DIAG, UPLO
16 * INTEGER LDA, LDAINV, N
17 * DOUBLE PRECISION RCOND, RESID
18 * ..
19 * .. Array Arguments ..
20 * DOUBLE PRECISION RWORK( * )
21 * COMPLEX*16 A( LDA, * ), AINV( LDAINV, * )
22 * ..
23 *
24 *
25 *> \par Purpose:
26 * =============
27 *>
28 *> \verbatim
29 *>
30 *> ZTRT01 computes the residual for a triangular matrix A times its
31 *> inverse:
32 *> RESID = norm( A*AINV - I ) / ( N * norm(A) * norm(AINV) * EPS ),
33 *> where EPS is the machine epsilon.
34 *> \endverbatim
35 *
36 * Arguments:
37 * ==========
38 *
39 *> \param[in] UPLO
40 *> \verbatim
41 *> UPLO is CHARACTER*1
42 *> Specifies whether the matrix A is upper or lower triangular.
43 *> = 'U': Upper triangular
44 *> = 'L': Lower triangular
45 *> \endverbatim
46 *>
47 *> \param[in] DIAG
48 *> \verbatim
49 *> DIAG is CHARACTER*1
50 *> Specifies whether or not the matrix A is unit triangular.
51 *> = 'N': Non-unit triangular
52 *> = 'U': Unit triangular
53 *> \endverbatim
54 *>
55 *> \param[in] N
56 *> \verbatim
57 *> N is INTEGER
58 *> The order of the matrix A. N >= 0.
59 *> \endverbatim
60 *>
61 *> \param[in] A
62 *> \verbatim
63 *> A is COMPLEX*16 array, dimension (LDA,N)
64 *> The triangular matrix A. If UPLO = 'U', the leading n by n
65 *> upper triangular part of the array A contains the upper
66 *> triangular matrix, and the strictly lower triangular part of
67 *> A is not referenced. If UPLO = 'L', the leading n by n lower
68 *> triangular part of the array A contains the lower triangular
69 *> matrix, and the strictly upper triangular part of A is not
70 *> referenced. If DIAG = 'U', the diagonal elements of A are
71 *> also not referenced and are assumed to be 1.
72 *> \endverbatim
73 *>
74 *> \param[in] LDA
75 *> \verbatim
76 *> LDA is INTEGER
77 *> The leading dimension of the array A. LDA >= max(1,N).
78 *> \endverbatim
79 *>
80 *> \param[in] AINV
81 *> \verbatim
82 *> AINV is COMPLEX*16 array, dimension (LDAINV,N)
83 *> On entry, the (triangular) inverse of the matrix A, in the
84 *> same storage format as A.
85 *> On exit, the contents of AINV are destroyed.
86 *> \endverbatim
87 *>
88 *> \param[in] LDAINV
89 *> \verbatim
90 *> LDAINV is INTEGER
91 *> The leading dimension of the array AINV. LDAINV >= max(1,N).
92 *> \endverbatim
93 *>
94 *> \param[out] RCOND
95 *> \verbatim
96 *> RCOND is DOUBLE PRECISION
97 *> The reciprocal condition number of A, computed as
98 *> 1/(norm(A) * norm(AINV)).
99 *> \endverbatim
100 *>
101 *> \param[out] RWORK
102 *> \verbatim
103 *> RWORK is DOUBLE PRECISION array, dimension (N)
104 *> \endverbatim
105 *>
106 *> \param[out] RESID
107 *> \verbatim
108 *> RESID is DOUBLE PRECISION
109 *> norm(A*AINV - I) / ( N * norm(A) * norm(AINV) * EPS )
110 *> \endverbatim
111 *
112 * Authors:
113 * ========
114 *
115 *> \author Univ. of Tennessee
116 *> \author Univ. of California Berkeley
117 *> \author Univ. of Colorado Denver
118 *> \author NAG Ltd.
119 *
120 *> \date November 2011
121 *
122 *> \ingroup complex16_lin
123 *
124 * =====================================================================
125  SUBROUTINE ztrt01( UPLO, DIAG, N, A, LDA, AINV, LDAINV, RCOND,
126  $ rwork, resid )
127 *
128 * -- LAPACK test routine (version 3.4.0) --
129 * -- LAPACK is a software package provided by Univ. of Tennessee, --
130 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
131 * November 2011
132 *
133 * .. Scalar Arguments ..
134  CHARACTER diag, uplo
135  INTEGER lda, ldainv, n
136  DOUBLE PRECISION rcond, resid
137 * ..
138 * .. Array Arguments ..
139  DOUBLE PRECISION rwork( * )
140  COMPLEX*16 a( lda, * ), ainv( ldainv, * )
141 * ..
142 *
143 * =====================================================================
144 *
145 * .. Parameters ..
146  DOUBLE PRECISION zero, one
147  parameter( zero = 0.0d+0, one = 1.0d+0 )
148 * ..
149 * .. Local Scalars ..
150  INTEGER j
151  DOUBLE PRECISION ainvnm, anorm, eps
152 * ..
153 * .. External Functions ..
154  LOGICAL lsame
155  DOUBLE PRECISION dlamch, zlantr
156  EXTERNAL lsame, dlamch, zlantr
157 * ..
158 * .. External Subroutines ..
159  EXTERNAL ztrmv
160 * ..
161 * .. Intrinsic Functions ..
162  INTRINSIC dble
163 * ..
164 * .. Executable Statements ..
165 *
166 * Quick exit if N = 0
167 *
168  IF( n.LE.0 ) THEN
169  rcond = one
170  resid = zero
171  return
172  END IF
173 *
174 * Exit with RESID = 1/EPS if ANORM = 0 or AINVNM = 0.
175 *
176  eps = dlamch( 'Epsilon' )
177  anorm = zlantr( '1', uplo, diag, n, n, a, lda, rwork )
178  ainvnm = zlantr( '1', uplo, diag, n, n, ainv, ldainv, rwork )
179  IF( anorm.LE.zero .OR. ainvnm.LE.zero ) THEN
180  rcond = zero
181  resid = one / eps
182  return
183  END IF
184  rcond = ( one / anorm ) / ainvnm
185 *
186 * Set the diagonal of AINV to 1 if AINV has unit diagonal.
187 *
188  IF( lsame( diag, 'U' ) ) THEN
189  DO 10 j = 1, n
190  ainv( j, j ) = one
191  10 continue
192  END IF
193 *
194 * Compute A * AINV, overwriting AINV.
195 *
196  IF( lsame( uplo, 'U' ) ) THEN
197  DO 20 j = 1, n
198  CALL ztrmv( 'Upper', 'No transpose', diag, j, a, lda,
199  $ ainv( 1, j ), 1 )
200  20 continue
201  ELSE
202  DO 30 j = 1, n
203  CALL ztrmv( 'Lower', 'No transpose', diag, n-j+1, a( j, j ),
204  $ lda, ainv( j, j ), 1 )
205  30 continue
206  END IF
207 *
208 * Subtract 1 from each diagonal element to form A*AINV - I.
209 *
210  DO 40 j = 1, n
211  ainv( j, j ) = ainv( j, j ) - one
212  40 continue
213 *
214 * Compute norm(A*AINV - I) / (N * norm(A) * norm(AINV) * EPS)
215 *
216  resid = zlantr( '1', uplo, 'Non-unit', n, n, ainv, ldainv, rwork )
217 *
218  resid = ( ( resid*rcond ) / dble( n ) ) / eps
219 *
220  return
221 *
222 * End of ZTRT01
223 *
224  END