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