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