001:       SUBROUTINE DGTCON( NORM, N, DL, D, DU, DU2, IPIV, ANORM, RCOND,
002:      $                   WORK, IWORK, 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 DLACN2 in place of DLACON, 5 Feb 03, SJH.
009: *
010: *     .. Scalar Arguments ..
011:       CHARACTER          NORM
012:       INTEGER            INFO, N
013:       DOUBLE PRECISION   ANORM, RCOND
014: *     ..
015: *     .. Array Arguments ..
016:       INTEGER            IPIV( * ), IWORK( * )
017:       DOUBLE PRECISION   D( * ), DL( * ), DU( * ), DU2( * ), WORK( * )
018: *     ..
019: *
020: *  Purpose
021: *  =======
022: *
023: *  DGTCON estimates the reciprocal of the condition number of a real
024: *  tridiagonal matrix A using the LU factorization as computed by
025: *  DGTTRF.
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) DOUBLE PRECISION array, dimension (N-1)
043: *          The (n-1) multipliers that define the matrix L from the
044: *          LU factorization of A as computed by DGTTRF.
045: *
046: *  D       (input) DOUBLE PRECISION 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) DOUBLE PRECISION array, dimension (N-1)
051: *          The (n-1) elements of the first superdiagonal of U.
052: *
053: *  DU2     (input) DOUBLE PRECISION 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) DOUBLE PRECISION
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) DOUBLE PRECISION
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) DOUBLE PRECISION array, dimension (2*N)
072: *
073: *  IWORK   (workspace) INTEGER array, dimension (N)
074: *
075: *  INFO    (output) INTEGER
076: *          = 0:  successful exit
077: *          < 0:  if INFO = -i, the i-th argument had an illegal value
078: *
079: *  =====================================================================
080: *
081: *     .. Parameters ..
082:       DOUBLE PRECISION   ONE, ZERO
083:       PARAMETER          ( ONE = 1.0D+0, ZERO = 0.0D+0 )
084: *     ..
085: *     .. Local Scalars ..
086:       LOGICAL            ONENRM
087:       INTEGER            I, KASE, KASE1
088:       DOUBLE PRECISION   AINVNM
089: *     ..
090: *     .. Local Arrays ..
091:       INTEGER            ISAVE( 3 )
092: *     ..
093: *     .. External Functions ..
094:       LOGICAL            LSAME
095:       EXTERNAL           LSAME
096: *     ..
097: *     .. External Subroutines ..
098:       EXTERNAL           DGTTRS, DLACN2, XERBLA
099: *     ..
100: *     .. Executable Statements ..
101: *
102: *     Test the input arguments.
103: *
104:       INFO = 0
105:       ONENRM = NORM.EQ.'1' .OR. LSAME( NORM, 'O' )
106:       IF( .NOT.ONENRM .AND. .NOT.LSAME( NORM, 'I' ) ) THEN
107:          INFO = -1
108:       ELSE IF( N.LT.0 ) THEN
109:          INFO = -2
110:       ELSE IF( ANORM.LT.ZERO ) THEN
111:          INFO = -8
112:       END IF
113:       IF( INFO.NE.0 ) THEN
114:          CALL XERBLA( 'DGTCON', -INFO )
115:          RETURN
116:       END IF
117: *
118: *     Quick return if possible
119: *
120:       RCOND = ZERO
121:       IF( N.EQ.0 ) THEN
122:          RCOND = ONE
123:          RETURN
124:       ELSE IF( ANORM.EQ.ZERO ) THEN
125:          RETURN
126:       END IF
127: *
128: *     Check that D(1:N) is non-zero.
129: *
130:       DO 10 I = 1, N
131:          IF( D( I ).EQ.ZERO )
132:      $      RETURN
133:    10 CONTINUE
134: *
135:       AINVNM = ZERO
136:       IF( ONENRM ) THEN
137:          KASE1 = 1
138:       ELSE
139:          KASE1 = 2
140:       END IF
141:       KASE = 0
142:    20 CONTINUE
143:       CALL DLACN2( N, WORK( N+1 ), WORK, IWORK, AINVNM, KASE, ISAVE )
144:       IF( KASE.NE.0 ) THEN
145:          IF( KASE.EQ.KASE1 ) THEN
146: *
147: *           Multiply by inv(U)*inv(L).
148: *
149:             CALL DGTTRS( 'No transpose', N, 1, DL, D, DU, DU2, IPIV,
150:      $                   WORK, N, INFO )
151:          ELSE
152: *
153: *           Multiply by inv(L')*inv(U').
154: *
155:             CALL DGTTRS( 'Transpose', N, 1, DL, D, DU, DU2, IPIV, WORK,
156:      $                   N, INFO )
157:          END IF
158:          GO TO 20
159:       END IF
160: *
161: *     Compute the estimate of the reciprocal condition number.
162: *
163:       IF( AINVNM.NE.ZERO )
164:      $   RCOND = ( ONE / AINVNM ) / ANORM
165: *
166:       RETURN
167: *
168: *     End of DGTCON
169: *
170:       END
171: