LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ spocon()

subroutine spocon ( character  uplo,
integer  n,
real, dimension( lda, * )  a,
integer  lda,
real  anorm,
real  rcond,
real, dimension( * )  work,
integer, dimension( * )  iwork,
integer  info 
)

SPOCON

Download SPOCON + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 SPOCON estimates the reciprocal of the condition number (in the
 1-norm) of a real symmetric positive definite matrix using the
 Cholesky factorization A = U**T*U or A = L*L**T computed by SPOTRF.

 An estimate is obtained for norm(inv(A)), and the reciprocal of the
 condition number is computed as RCOND = 1 / (ANORM * norm(inv(A))).
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          = 'U':  Upper triangle of A is stored;
          = 'L':  Lower triangle of A is stored.
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.
[in]A
          A is REAL array, dimension (LDA,N)
          The triangular factor U or L from the Cholesky factorization
          A = U**T*U or A = L*L**T, as computed by SPOTRF.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,N).
[in]ANORM
          ANORM is REAL
          The 1-norm (or infinity-norm) of the symmetric matrix A.
[out]RCOND
          RCOND is REAL
          The reciprocal of the condition number of the matrix A,
          computed as RCOND = 1/(ANORM * AINVNM), where AINVNM is an
          estimate of the 1-norm of inv(A) computed in this routine.
[out]WORK
          WORK is REAL array, dimension (3*N)
[out]IWORK
          IWORK is INTEGER array, dimension (N)
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0:  if INFO = -i, the i-th argument had an illegal value
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 119 of file spocon.f.

121*
122* -- LAPACK computational routine --
123* -- LAPACK is a software package provided by Univ. of Tennessee, --
124* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
125*
126* .. Scalar Arguments ..
127 CHARACTER UPLO
128 INTEGER INFO, LDA, N
129 REAL ANORM, RCOND
130* ..
131* .. Array Arguments ..
132 INTEGER IWORK( * )
133 REAL A( LDA, * ), WORK( * )
134* ..
135*
136* =====================================================================
137*
138* .. Parameters ..
139 REAL ONE, ZERO
140 parameter( one = 1.0e+0, zero = 0.0e+0 )
141* ..
142* .. Local Scalars ..
143 LOGICAL UPPER
144 CHARACTER NORMIN
145 INTEGER IX, KASE
146 REAL AINVNM, SCALE, SCALEL, SCALEU, SMLNUM
147* ..
148* .. Local Arrays ..
149 INTEGER ISAVE( 3 )
150* ..
151* .. External Functions ..
152 LOGICAL LSAME
153 INTEGER ISAMAX
154 REAL SLAMCH
155 EXTERNAL lsame, isamax, slamch
156* ..
157* .. External Subroutines ..
158 EXTERNAL slacn2, slatrs, srscl, xerbla
159* ..
160* .. Intrinsic Functions ..
161 INTRINSIC abs, max
162* ..
163* .. Executable Statements ..
164*
165* Test the input parameters.
166*
167 info = 0
168 upper = lsame( uplo, 'U' )
169 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
170 info = -1
171 ELSE IF( n.LT.0 ) THEN
172 info = -2
173 ELSE IF( lda.LT.max( 1, n ) ) THEN
174 info = -4
175 ELSE IF( anorm.LT.zero ) THEN
176 info = -5
177 END IF
178 IF( info.NE.0 ) THEN
179 CALL xerbla( 'SPOCON', -info )
180 RETURN
181 END IF
182*
183* Quick return if possible
184*
185 rcond = zero
186 IF( n.EQ.0 ) THEN
187 rcond = one
188 RETURN
189 ELSE IF( anorm.EQ.zero ) THEN
190 RETURN
191 END IF
192*
193 smlnum = slamch( 'Safe minimum' )
194*
195* Estimate the 1-norm of inv(A).
196*
197 kase = 0
198 normin = 'N'
199 10 CONTINUE
200 CALL slacn2( n, work( n+1 ), work, iwork, ainvnm, kase, isave )
201 IF( kase.NE.0 ) THEN
202 IF( upper ) THEN
203*
204* Multiply by inv(U**T).
205*
206 CALL slatrs( 'Upper', 'Transpose', 'Non-unit', normin, n, a,
207 $ lda, work, scalel, work( 2*n+1 ), info )
208 normin = 'Y'
209*
210* Multiply by inv(U).
211*
212 CALL slatrs( 'Upper', 'No transpose', 'Non-unit', normin, n,
213 $ a, lda, work, scaleu, work( 2*n+1 ), info )
214 ELSE
215*
216* Multiply by inv(L).
217*
218 CALL slatrs( 'Lower', 'No transpose', 'Non-unit', normin, n,
219 $ a, lda, work, scalel, work( 2*n+1 ), info )
220 normin = 'Y'
221*
222* Multiply by inv(L**T).
223*
224 CALL slatrs( 'Lower', 'Transpose', 'Non-unit', normin, n, a,
225 $ lda, work, scaleu, work( 2*n+1 ), info )
226 END IF
227*
228* Multiply by 1/SCALE if doing so will not cause overflow.
229*
230 scale = scalel*scaleu
231 IF( scale.NE.one ) THEN
232 ix = isamax( n, work, 1 )
233 IF( scale.LT.abs( work( ix ) )*smlnum .OR. scale.EQ.zero )
234 $ GO TO 20
235 CALL srscl( n, scale, work, 1 )
236 END IF
237 GO TO 10
238 END IF
239*
240* Compute the estimate of the reciprocal condition number.
241*
242 IF( ainvnm.NE.zero )
243 $ rcond = ( one / ainvnm ) / anorm
244*
245 20 CONTINUE
246 RETURN
247*
248* End of SPOCON
249*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function isamax(n, sx, incx)
ISAMAX
Definition isamax.f:71
subroutine slacn2(n, v, x, isgn, est, kase, isave)
SLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
Definition slacn2.f:136
real function slamch(cmach)
SLAMCH
Definition slamch.f:68
subroutine slatrs(uplo, trans, diag, normin, n, a, lda, x, scale, cnorm, info)
SLATRS solves a triangular system of equations with the scale factor set to prevent overflow.
Definition slatrs.f:238
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine srscl(n, sa, sx, incx)
SRSCL multiplies a vector by the reciprocal of a real scalar.
Definition srscl.f:84
Here is the call graph for this function:
Here is the caller graph for this function: