LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
csyt03.f
Go to the documentation of this file.
1*> \brief \b CSYT03
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 CSYT03( UPLO, N, A, LDA, AINV, LDAINV, WORK, LDWORK,
12* RWORK, RCOND, RESID )
13*
14* .. Scalar Arguments ..
15* CHARACTER UPLO
16* INTEGER LDA, LDAINV, LDWORK, N
17* REAL RCOND, RESID
18* ..
19* .. Array Arguments ..
20* REAL RWORK( * )
21* COMPLEX A( LDA, * ), AINV( LDAINV, * ),
22* $ WORK( LDWORK, * )
23* ..
24*
25*
26*> \par Purpose:
27* =============
28*>
29*> \verbatim
30*>
31*> CSYT03 computes the residual for a complex symmetric matrix times
32*> its inverse:
33*> norm( I - A*AINV ) / ( N * norm(A) * norm(AINV) * EPS )
34*> where EPS is the machine epsilon.
35*> \endverbatim
36*
37* Arguments:
38* ==========
39*
40*> \param[in] UPLO
41*> \verbatim
42*> UPLO is CHARACTER*1
43*> Specifies whether the upper or lower triangular part of the
44*> complex symmetric matrix A is stored:
45*> = 'U': Upper triangular
46*> = 'L': Lower triangular
47*> \endverbatim
48*>
49*> \param[in] N
50*> \verbatim
51*> N is INTEGER
52*> The number of rows and columns of the matrix A. N >= 0.
53*> \endverbatim
54*>
55*> \param[in] A
56*> \verbatim
57*> A is COMPLEX array, dimension (LDA,N)
58*> The original complex symmetric matrix A.
59*> \endverbatim
60*>
61*> \param[in] LDA
62*> \verbatim
63*> LDA is INTEGER
64*> The leading dimension of the array A. LDA >= max(1,N)
65*> \endverbatim
66*>
67*> \param[in,out] AINV
68*> \verbatim
69*> AINV is COMPLEX array, dimension (LDAINV,N)
70*> On entry, the inverse of the matrix A, stored as a symmetric
71*> matrix in the same format as A.
72*> In this version, AINV is expanded into a full matrix and
73*> multiplied by A, so the opposing triangle of AINV will be
74*> changed; i.e., if the upper triangular part of AINV is
75*> stored, the lower triangular part will be used as work space.
76*> \endverbatim
77*>
78*> \param[in] LDAINV
79*> \verbatim
80*> LDAINV is INTEGER
81*> The leading dimension of the array AINV. LDAINV >= max(1,N).
82*> \endverbatim
83*>
84*> \param[out] WORK
85*> \verbatim
86*> WORK is COMPLEX array, dimension (LDWORK,N)
87*> \endverbatim
88*>
89*> \param[in] LDWORK
90*> \verbatim
91*> LDWORK is INTEGER
92*> The leading dimension of the array WORK. LDWORK >= max(1,N).
93*> \endverbatim
94*>
95*> \param[out] RWORK
96*> \verbatim
97*> RWORK is REAL array, dimension (N)
98*> \endverbatim
99*>
100*> \param[out] RCOND
101*> \verbatim
102*> RCOND is REAL
103*> The reciprocal of the condition number of A, computed as
104*> RCOND = 1/ (norm(A) * norm(AINV)).
105*> \endverbatim
106*>
107*> \param[out] RESID
108*> \verbatim
109*> RESID is REAL
110*> norm(I - A*AINV) / ( N * norm(A) * norm(AINV) * EPS )
111*> \endverbatim
112*
113* Authors:
114* ========
115*
116*> \author Univ. of Tennessee
117*> \author Univ. of California Berkeley
118*> \author Univ. of Colorado Denver
119*> \author NAG Ltd.
120*
121*> \ingroup complex_lin
122*
123* =====================================================================
124 SUBROUTINE csyt03( UPLO, N, A, LDA, AINV, LDAINV, WORK, LDWORK,
125 $ RWORK, RCOND, RESID )
126*
127* -- LAPACK test routine --
128* -- LAPACK is a software package provided by Univ. of Tennessee, --
129* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
130*
131* .. Scalar Arguments ..
132 CHARACTER UPLO
133 INTEGER LDA, LDAINV, LDWORK, N
134 REAL RCOND, RESID
135* ..
136* .. Array Arguments ..
137 REAL RWORK( * )
138 COMPLEX A( LDA, * ), AINV( LDAINV, * ),
139 $ work( ldwork, * )
140* ..
141*
142* =====================================================================
143*
144*
145* .. Parameters ..
146 REAL ZERO, ONE
147 parameter( zero = 0.0e+0, one = 1.0e+0 )
148 COMPLEX CZERO, CONE
149 parameter( czero = ( 0.0e+0, 0.0e+0 ),
150 $ cone = ( 1.0e+0, 0.0e+0 ) )
151* ..
152* .. Local Scalars ..
153 INTEGER I, J
154 REAL AINVNM, ANORM, EPS
155* ..
156* .. External Functions ..
157 LOGICAL LSAME
158 REAL CLANGE, CLANSY, SLAMCH
159 EXTERNAL lsame, clange, clansy, slamch
160* ..
161* .. External Subroutines ..
162 EXTERNAL csymm
163* ..
164* .. Intrinsic Functions ..
165 INTRINSIC real
166* ..
167* .. Executable Statements ..
168*
169* Quick exit if N = 0
170*
171 IF( n.LE.0 ) THEN
172 rcond = one
173 resid = zero
174 RETURN
175 END IF
176*
177* Exit with RESID = 1/EPS if ANORM = 0 or AINVNM = 0.
178*
179 eps = slamch( 'Epsilon' )
180 anorm = clansy( '1', uplo, n, a, lda, rwork )
181 ainvnm = clansy( '1', uplo, n, ainv, ldainv, rwork )
182 IF( anorm.LE.zero .OR. ainvnm.LE.zero ) THEN
183 rcond = zero
184 resid = one / eps
185 RETURN
186 END IF
187 rcond = ( one/anorm ) / ainvnm
188*
189* Expand AINV into a full matrix and call CSYMM to multiply
190* AINV on the left by A (store the result in WORK).
191*
192 IF( lsame( uplo, 'U' ) ) THEN
193 DO 20 j = 1, n
194 DO 10 i = 1, j - 1
195 ainv( j, i ) = ainv( i, j )
196 10 CONTINUE
197 20 CONTINUE
198 ELSE
199 DO 40 j = 1, n
200 DO 30 i = j + 1, n
201 ainv( j, i ) = ainv( i, j )
202 30 CONTINUE
203 40 CONTINUE
204 END IF
205 CALL csymm( 'Left', uplo, n, n, -cone, a, lda, ainv, ldainv,
206 $ czero, work, ldwork )
207*
208* Add the identity matrix to WORK .
209*
210 DO 50 i = 1, n
211 work( i, i ) = work( i, i ) + cone
212 50 CONTINUE
213*
214* Compute norm(I - A*AINV) / (N * norm(A) * norm(AINV) * EPS)
215*
216 resid = clange( '1', n, n, work, ldwork, rwork )
217*
218 resid = ( ( resid*rcond )/eps ) / real( n )
219*
220 RETURN
221*
222* End of CSYT03
223*
224 END
subroutine csyt03(uplo, n, a, lda, ainv, ldainv, work, ldwork, rwork, rcond, resid)
CSYT03
Definition csyt03.f:126
subroutine csymm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)
CSYMM
Definition csymm.f:189