001:       SUBROUTINE CGTCON( NORM, N, DL, D, DU, DU2, IPIV, ANORM, RCOND,
002:      $                   WORK, INFO )
003: *
004: *  -- LAPACK routine (version 3.2) --
005: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
006: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
007: *     November 2006
008: *
009: *     Modified to call CLACN2 in place of CLACON, 10 Feb 03, SJH.
010: *
011: *     .. Scalar Arguments ..
012:       CHARACTER          NORM
013:       INTEGER            INFO, N
014:       REAL               ANORM, RCOND
015: *     ..
016: *     .. Array Arguments ..
017:       INTEGER            IPIV( * )
018:       COMPLEX            D( * ), DL( * ), DU( * ), DU2( * ), WORK( * )
019: *     ..
020: *
021: *  Purpose
022: *  =======
023: *
024: *  CGTCON estimates the reciprocal of the condition number of a complex
025: *  tridiagonal matrix A using the LU factorization as computed by
026: *  CGTTRF.
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: *  NORM    (input) CHARACTER*1
035: *          Specifies whether the 1-norm condition number or the
036: *          infinity-norm condition number is required:
037: *          = '1' or 'O':  1-norm;
038: *          = 'I':         Infinity-norm.
039: *
040: *  N       (input) INTEGER
041: *          The order of the matrix A.  N >= 0.
042: *
043: *  DL      (input) COMPLEX array, dimension (N-1)
044: *          The (n-1) multipliers that define the matrix L from the
045: *          LU factorization of A as computed by CGTTRF.
046: *
047: *  D       (input) COMPLEX array, dimension (N)
048: *          The n diagonal elements of the upper triangular matrix U from
049: *          the LU factorization of A.
050: *
051: *  DU      (input) COMPLEX array, dimension (N-1)
052: *          The (n-1) elements of the first superdiagonal of U.
053: *
054: *  DU2     (input) COMPLEX array, dimension (N-2)
055: *          The (n-2) elements of the second superdiagonal of U.
056: *
057: *  IPIV    (input) INTEGER array, dimension (N)
058: *          The pivot indices; for 1 <= i <= n, row i of the matrix was
059: *          interchanged with row IPIV(i).  IPIV(i) will always be either
060: *          i or i+1; IPIV(i) = i indicates a row interchange was not
061: *          required.
062: *
063: *  ANORM   (input) REAL
064: *          If NORM = '1' or 'O', the 1-norm of the original matrix A.
065: *          If NORM = 'I', the infinity-norm of the original matrix A.
066: *
067: *  RCOND   (output) REAL
068: *          The reciprocal of the condition number of the matrix A,
069: *          computed as RCOND = 1/(ANORM * AINVNM), where AINVNM is an
070: *          estimate of the 1-norm of inv(A) computed in this routine.
071: *
072: *  WORK    (workspace) COMPLEX array, dimension (2*N)
073: *
074: *  INFO    (output) INTEGER
075: *          = 0:  successful exit
076: *          < 0:  if INFO = -i, the i-th argument had an illegal value
077: *
078: *  =====================================================================
079: *
080: *     .. Parameters ..
081:       REAL               ONE, ZERO
082:       PARAMETER          ( ONE = 1.0E+0, ZERO = 0.0E+0 )
083: *     ..
084: *     .. Local Scalars ..
085:       LOGICAL            ONENRM
086:       INTEGER            I, KASE, KASE1
087:       REAL               AINVNM
088: *     ..
089: *     .. Local Arrays ..
090:       INTEGER            ISAVE( 3 )
091: *     ..
092: *     .. External Functions ..
093:       LOGICAL            LSAME
094:       EXTERNAL           LSAME
095: *     ..
096: *     .. External Subroutines ..
097:       EXTERNAL           CGTTRS, CLACN2, XERBLA
098: *     ..
099: *     .. Intrinsic Functions ..
100:       INTRINSIC          CMPLX
101: *     ..
102: *     .. Executable Statements ..
103: *
104: *     Test the input arguments.
105: *
106:       INFO = 0
107:       ONENRM = NORM.EQ.'1' .OR. LSAME( NORM, 'O' )
108:       IF( .NOT.ONENRM .AND. .NOT.LSAME( NORM, 'I' ) ) THEN
109:          INFO = -1
110:       ELSE IF( N.LT.0 ) THEN
111:          INFO = -2
112:       ELSE IF( ANORM.LT.ZERO ) THEN
113:          INFO = -8
114:       END IF
115:       IF( INFO.NE.0 ) THEN
116:          CALL XERBLA( 'CGTCON', -INFO )
117:          RETURN
118:       END IF
119: *
120: *     Quick return if possible
121: *
122:       RCOND = ZERO
123:       IF( N.EQ.0 ) THEN
124:          RCOND = ONE
125:          RETURN
126:       ELSE IF( ANORM.EQ.ZERO ) THEN
127:          RETURN
128:       END IF
129: *
130: *     Check that D(1:N) is non-zero.
131: *
132:       DO 10 I = 1, N
133:          IF( D( I ).EQ.CMPLX( ZERO ) )
134:      $      RETURN
135:    10 CONTINUE
136: *
137:       AINVNM = ZERO
138:       IF( ONENRM ) THEN
139:          KASE1 = 1
140:       ELSE
141:          KASE1 = 2
142:       END IF
143:       KASE = 0
144:    20 CONTINUE
145:       CALL CLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
146:       IF( KASE.NE.0 ) THEN
147:          IF( KASE.EQ.KASE1 ) THEN
148: *
149: *           Multiply by inv(U)*inv(L).
150: *
151:             CALL CGTTRS( 'No transpose', N, 1, DL, D, DU, DU2, IPIV,
152:      $                   WORK, N, INFO )
153:          ELSE
154: *
155: *           Multiply by inv(L')*inv(U').
156: *
157:             CALL CGTTRS( 'Conjugate transpose', N, 1, DL, D, DU, DU2,
158:      $                   IPIV, WORK, N, INFO )
159:          END IF
160:          GO TO 20
161:       END IF
162: *
163: *     Compute the estimate of the reciprocal condition number.
164: *
165:       IF( AINVNM.NE.ZERO )
166:      $   RCOND = ( ONE / AINVNM ) / ANORM
167: *
168:       RETURN
169: *
170: *     End of CGTCON
171: *
172:       END
173: