001:       SUBROUTINE SPPCON( UPLO, N, AP, ANORM, RCOND, WORK, IWORK, INFO )
002: *
003: *  -- LAPACK routine (version 3.2) --
004: *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
005: *     November 2006
006: *
007: *     Modified to call SLACN2 in place of SLACON, 7 Feb 03, SJH.
008: *
009: *     .. Scalar Arguments ..
010:       CHARACTER          UPLO
011:       INTEGER            INFO, N
012:       REAL               ANORM, RCOND
013: *     ..
014: *     .. Array Arguments ..
015:       INTEGER            IWORK( * )
016:       REAL               AP( * ), WORK( * )
017: *     ..
018: *
019: *  Purpose
020: *  =======
021: *
022: *  SPPCON estimates the reciprocal of the condition number (in the
023: *  1-norm) of a real symmetric positive definite packed matrix using
024: *  the Cholesky factorization A = U**T*U or A = L*L**T computed by
025: *  SPPTRF.
026: *
027: *  An estimate is obtained for norm(inv(A)), and the reciprocal of the
028: *  condition number is computed as RCOND = 1 / (ANORM * norm(inv(A))).
029: *
030: *  Arguments
031: *  =========
032: *
033: *  UPLO    (input) CHARACTER*1
034: *          = 'U':  Upper triangle of A is stored;
035: *          = 'L':  Lower triangle of A is stored.
036: *
037: *  N       (input) INTEGER
038: *          The order of the matrix A.  N >= 0.
039: *
040: *  AP      (input) REAL array, dimension (N*(N+1)/2)
041: *          The triangular factor U or L from the Cholesky factorization
042: *          A = U**T*U or A = L*L**T, packed columnwise in a linear
043: *          array.  The j-th column of U or L is stored in the array AP
044: *          as follows:
045: *          if UPLO = 'U', AP(i + (j-1)*j/2) = U(i,j) for 1<=i<=j;
046: *          if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = L(i,j) for j<=i<=n.
047: *
048: *  ANORM   (input) REAL
049: *          The 1-norm (or infinity-norm) of the symmetric matrix A.
050: *
051: *  RCOND   (output) REAL
052: *          The reciprocal of the condition number of the matrix A,
053: *          computed as RCOND = 1/(ANORM * AINVNM), where AINVNM is an
054: *          estimate of the 1-norm of inv(A) computed in this routine.
055: *
056: *  WORK    (workspace) REAL array, dimension (3*N)
057: *
058: *  IWORK   (workspace) INTEGER array, dimension (N)
059: *
060: *  INFO    (output) INTEGER
061: *          = 0:  successful exit
062: *          < 0:  if INFO = -i, the i-th argument had an illegal value
063: *
064: *  =====================================================================
065: *
066: *     .. Parameters ..
067:       REAL               ONE, ZERO
068:       PARAMETER          ( ONE = 1.0E+0, ZERO = 0.0E+0 )
069: *     ..
070: *     .. Local Scalars ..
071:       LOGICAL            UPPER
072:       CHARACTER          NORMIN
073:       INTEGER            IX, KASE
074:       REAL               AINVNM, SCALE, SCALEL, SCALEU, SMLNUM
075: *     ..
076: *     .. Local Arrays ..
077:       INTEGER            ISAVE( 3 )
078: *     ..
079: *     .. External Functions ..
080:       LOGICAL            LSAME
081:       INTEGER            ISAMAX
082:       REAL               SLAMCH
083:       EXTERNAL           LSAME, ISAMAX, SLAMCH
084: *     ..
085: *     .. External Subroutines ..
086:       EXTERNAL           SLACN2, SLATPS, SRSCL, XERBLA
087: *     ..
088: *     .. Intrinsic Functions ..
089:       INTRINSIC          ABS
090: *     ..
091: *     .. Executable Statements ..
092: *
093: *     Test the input parameters.
094: *
095:       INFO = 0
096:       UPPER = LSAME( UPLO, 'U' )
097:       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
098:          INFO = -1
099:       ELSE IF( N.LT.0 ) THEN
100:          INFO = -2
101:       ELSE IF( ANORM.LT.ZERO ) THEN
102:          INFO = -4
103:       END IF
104:       IF( INFO.NE.0 ) THEN
105:          CALL XERBLA( 'SPPCON', -INFO )
106:          RETURN
107:       END IF
108: *
109: *     Quick return if possible
110: *
111:       RCOND = ZERO
112:       IF( N.EQ.0 ) THEN
113:          RCOND = ONE
114:          RETURN
115:       ELSE IF( ANORM.EQ.ZERO ) THEN
116:          RETURN
117:       END IF
118: *
119:       SMLNUM = SLAMCH( 'Safe minimum' )
120: *
121: *     Estimate the 1-norm of the inverse.
122: *
123:       KASE = 0
124:       NORMIN = 'N'
125:    10 CONTINUE
126:       CALL SLACN2( N, WORK( N+1 ), WORK, IWORK, AINVNM, KASE, ISAVE )
127:       IF( KASE.NE.0 ) THEN
128:          IF( UPPER ) THEN
129: *
130: *           Multiply by inv(U').
131: *
132:             CALL SLATPS( 'Upper', 'Transpose', 'Non-unit', NORMIN, N,
133:      $                   AP, WORK, SCALEL, WORK( 2*N+1 ), INFO )
134:             NORMIN = 'Y'
135: *
136: *           Multiply by inv(U).
137: *
138:             CALL SLATPS( 'Upper', 'No transpose', 'Non-unit', NORMIN, N,
139:      $                   AP, WORK, SCALEU, WORK( 2*N+1 ), INFO )
140:          ELSE
141: *
142: *           Multiply by inv(L).
143: *
144:             CALL SLATPS( 'Lower', 'No transpose', 'Non-unit', NORMIN, N,
145:      $                   AP, WORK, SCALEL, WORK( 2*N+1 ), INFO )
146:             NORMIN = 'Y'
147: *
148: *           Multiply by inv(L').
149: *
150:             CALL SLATPS( 'Lower', 'Transpose', 'Non-unit', NORMIN, N,
151:      $                   AP, WORK, SCALEU, WORK( 2*N+1 ), INFO )
152:          END IF
153: *
154: *        Multiply by 1/SCALE if doing so will not cause overflow.
155: *
156:          SCALE = SCALEL*SCALEU
157:          IF( SCALE.NE.ONE ) THEN
158:             IX = ISAMAX( N, WORK, 1 )
159:             IF( SCALE.LT.ABS( WORK( IX ) )*SMLNUM .OR. SCALE.EQ.ZERO )
160:      $         GO TO 20
161:             CALL SRSCL( N, SCALE, WORK, 1 )
162:          END IF
163:          GO TO 10
164:       END IF
165: *
166: *     Compute the estimate of the reciprocal condition number.
167: *
168:       IF( AINVNM.NE.ZERO )
169:      $   RCOND = ( ONE / AINVNM ) / ANORM
170: *
171:    20 CONTINUE
172:       RETURN
173: *
174: *     End of SPPCON
175: *
176:       END
177: