LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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.
Date
November 2011

Definition at line 123 of file spocon.f.

123 *
124 * -- LAPACK computational routine (version 3.4.0) --
125 * -- LAPACK is a software package provided by Univ. of Tennessee, --
126 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
127 * November 2011
128 *
129 * .. Scalar Arguments ..
130  CHARACTER uplo
131  INTEGER info, lda, n
132  REAL anorm, rcond
133 * ..
134 * .. Array Arguments ..
135  INTEGER iwork( * )
136  REAL a( lda, * ), work( * )
137 * ..
138 *
139 * =====================================================================
140 *
141 * .. Parameters ..
142  REAL one, zero
143  parameter ( one = 1.0e+0, zero = 0.0e+0 )
144 * ..
145 * .. Local Scalars ..
146  LOGICAL upper
147  CHARACTER normin
148  INTEGER ix, kase
149  REAL ainvnm, scale, scalel, scaleu, smlnum
150 * ..
151 * .. Local Arrays ..
152  INTEGER isave( 3 )
153 * ..
154 * .. External Functions ..
155  LOGICAL lsame
156  INTEGER isamax
157  REAL slamch
158  EXTERNAL lsame, isamax, slamch
159 * ..
160 * .. External Subroutines ..
161  EXTERNAL slacn2, slatrs, srscl, xerbla
162 * ..
163 * .. Intrinsic Functions ..
164  INTRINSIC abs, max
165 * ..
166 * .. Executable Statements ..
167 *
168 * Test the input parameters.
169 *
170  info = 0
171  upper = lsame( uplo, 'U' )
172  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
173  info = -1
174  ELSE IF( n.LT.0 ) THEN
175  info = -2
176  ELSE IF( lda.LT.max( 1, n ) ) THEN
177  info = -4
178  ELSE IF( anorm.LT.zero ) THEN
179  info = -5
180  END IF
181  IF( info.NE.0 ) THEN
182  CALL xerbla( 'SPOCON', -info )
183  RETURN
184  END IF
185 *
186 * Quick return if possible
187 *
188  rcond = zero
189  IF( n.EQ.0 ) THEN
190  rcond = one
191  RETURN
192  ELSE IF( anorm.EQ.zero ) THEN
193  RETURN
194  END IF
195 *
196  smlnum = slamch( 'Safe minimum' )
197 *
198 * Estimate the 1-norm of inv(A).
199 *
200  kase = 0
201  normin = 'N'
202  10 CONTINUE
203  CALL slacn2( n, work( n+1 ), work, iwork, ainvnm, kase, isave )
204  IF( kase.NE.0 ) THEN
205  IF( upper ) THEN
206 *
207 * Multiply by inv(U**T).
208 *
209  CALL slatrs( 'Upper', 'Transpose', 'Non-unit', normin, n, a,
210  $ lda, work, scalel, work( 2*n+1 ), info )
211  normin = 'Y'
212 *
213 * Multiply by inv(U).
214 *
215  CALL slatrs( 'Upper', 'No transpose', 'Non-unit', normin, n,
216  $ a, lda, work, scaleu, work( 2*n+1 ), info )
217  ELSE
218 *
219 * Multiply by inv(L).
220 *
221  CALL slatrs( 'Lower', 'No transpose', 'Non-unit', normin, n,
222  $ a, lda, work, scalel, work( 2*n+1 ), info )
223  normin = 'Y'
224 *
225 * Multiply by inv(L**T).
226 *
227  CALL slatrs( 'Lower', 'Transpose', 'Non-unit', normin, n, a,
228  $ lda, work, scaleu, work( 2*n+1 ), info )
229  END IF
230 *
231 * Multiply by 1/SCALE if doing so will not cause overflow.
232 *
233  scale = scalel*scaleu
234  IF( scale.NE.one ) THEN
235  ix = isamax( n, work, 1 )
236  IF( scale.LT.abs( work( ix ) )*smlnum .OR. scale.EQ.zero )
237  $ GO TO 20
238  CALL srscl( n, scale, work, 1 )
239  END IF
240  GO TO 10
241  END IF
242 *
243 * Compute the estimate of the reciprocal condition number.
244 *
245  IF( ainvnm.NE.zero )
246  $ rcond = ( one / ainvnm ) / anorm
247 *
248  20 CONTINUE
249  RETURN
250 *
251 * End of SPOCON
252 *
subroutine srscl(N, SA, SX, INCX)
SRSCL multiplies a vector by the reciprocal of a real scalar.
Definition: srscl.f:86
integer function isamax(N, SX, INCX)
ISAMAX
Definition: isamax.f:53
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
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:138
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:240
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:69
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: