LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine sppcon ( character  UPLO,
integer  N,
real, dimension( * )  AP,
real  ANORM,
real  RCOND,
real, dimension( * )  WORK,
integer, dimension( * )  IWORK,
integer  INFO 
)

SPPCON

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

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

 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]AP
          AP is REAL array, dimension (N*(N+1)/2)
          The triangular factor U or L from the Cholesky factorization
          A = U**T*U or A = L*L**T, packed columnwise in a linear
          array.  The j-th column of U or L is stored in the array AP
          as follows:
          if UPLO = 'U', AP(i + (j-1)*j/2) = U(i,j) for 1<=i<=j;
          if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = L(i,j) for j<=i<=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 120 of file sppcon.f.

120 *
121 * -- LAPACK computational routine (version 3.4.0) --
122 * -- LAPACK is a software package provided by Univ. of Tennessee, --
123 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
124 * November 2011
125 *
126 * .. Scalar Arguments ..
127  CHARACTER uplo
128  INTEGER info, n
129  REAL anorm, rcond
130 * ..
131 * .. Array Arguments ..
132  INTEGER iwork( * )
133  REAL ap( * ), 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, slatps, srscl, xerbla
159 * ..
160 * .. Intrinsic Functions ..
161  INTRINSIC abs
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( anorm.LT.zero ) THEN
174  info = -4
175  END IF
176  IF( info.NE.0 ) THEN
177  CALL xerbla( 'SPPCON', -info )
178  RETURN
179  END IF
180 *
181 * Quick return if possible
182 *
183  rcond = zero
184  IF( n.EQ.0 ) THEN
185  rcond = one
186  RETURN
187  ELSE IF( anorm.EQ.zero ) THEN
188  RETURN
189  END IF
190 *
191  smlnum = slamch( 'Safe minimum' )
192 *
193 * Estimate the 1-norm of the inverse.
194 *
195  kase = 0
196  normin = 'N'
197  10 CONTINUE
198  CALL slacn2( n, work( n+1 ), work, iwork, ainvnm, kase, isave )
199  IF( kase.NE.0 ) THEN
200  IF( upper ) THEN
201 *
202 * Multiply by inv(U**T).
203 *
204  CALL slatps( 'Upper', 'Transpose', 'Non-unit', normin, n,
205  $ ap, work, scalel, work( 2*n+1 ), info )
206  normin = 'Y'
207 *
208 * Multiply by inv(U).
209 *
210  CALL slatps( 'Upper', 'No transpose', 'Non-unit', normin, n,
211  $ ap, work, scaleu, work( 2*n+1 ), info )
212  ELSE
213 *
214 * Multiply by inv(L).
215 *
216  CALL slatps( 'Lower', 'No transpose', 'Non-unit', normin, n,
217  $ ap, work, scalel, work( 2*n+1 ), info )
218  normin = 'Y'
219 *
220 * Multiply by inv(L**T).
221 *
222  CALL slatps( 'Lower', 'Transpose', 'Non-unit', normin, n,
223  $ ap, work, scaleu, work( 2*n+1 ), info )
224  END IF
225 *
226 * Multiply by 1/SCALE if doing so will not cause overflow.
227 *
228  scale = scalel*scaleu
229  IF( scale.NE.one ) THEN
230  ix = isamax( n, work, 1 )
231  IF( scale.LT.abs( work( ix ) )*smlnum .OR. scale.EQ.zero )
232  $ GO TO 20
233  CALL srscl( n, scale, work, 1 )
234  END IF
235  GO TO 10
236  END IF
237 *
238 * Compute the estimate of the reciprocal condition number.
239 *
240  IF( ainvnm.NE.zero )
241  $ rcond = ( one / ainvnm ) / anorm
242 *
243  20 CONTINUE
244  RETURN
245 *
246 * End of SPPCON
247 *
subroutine srscl(N, SA, SX, INCX)
SRSCL multiplies a vector by the reciprocal of a real scalar.
Definition: srscl.f:86
subroutine slatps(UPLO, TRANS, DIAG, NORMIN, N, AP, X, SCALE, CNORM, INFO)
SLATPS solves a triangular system of equations with the matrix held in packed storage.
Definition: slatps.f:231
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
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: