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