001:       SUBROUTINE DGTCON( NORM, N, DL, D, DU, DU2, IPIV, ANORM, RCOND,
002:      $                   WORK, IWORK, 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 DLACN2 in place of DLACON, 5 Feb 03, SJH.
010: *
011: *     .. Scalar Arguments ..
012:       CHARACTER          NORM
013:       INTEGER            INFO, N
014:       DOUBLE PRECISION   ANORM, RCOND
015: *     ..
016: *     .. Array Arguments ..
017:       INTEGER            IPIV( * ), IWORK( * )
018:       DOUBLE PRECISION   D( * ), DL( * ), DU( * ), DU2( * ), WORK( * )
019: *     ..
020: *
021: *  Purpose
022: *  =======
023: *
024: *  DGTCON estimates the reciprocal of the condition number of a real
025: *  tridiagonal matrix A using the LU factorization as computed by
026: *  DGTTRF.
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) DOUBLE PRECISION array, dimension (N-1)
044: *          The (n-1) multipliers that define the matrix L from the
045: *          LU factorization of A as computed by DGTTRF.
046: *
047: *  D       (input) DOUBLE PRECISION 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) DOUBLE PRECISION array, dimension (N-1)
052: *          The (n-1) elements of the first superdiagonal of U.
053: *
054: *  DU2     (input) DOUBLE PRECISION 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) DOUBLE PRECISION
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) DOUBLE PRECISION
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) DOUBLE PRECISION array, dimension (2*N)
073: *
074: *  IWORK   (workspace) INTEGER array, dimension (N)
075: *
076: *  INFO    (output) INTEGER
077: *          = 0:  successful exit
078: *          < 0:  if INFO = -i, the i-th argument had an illegal value
079: *
080: *  =====================================================================
081: *
082: *     .. Parameters ..
083:       DOUBLE PRECISION   ONE, ZERO
084:       PARAMETER          ( ONE = 1.0D+0, ZERO = 0.0D+0 )
085: *     ..
086: *     .. Local Scalars ..
087:       LOGICAL            ONENRM
088:       INTEGER            I, KASE, KASE1
089:       DOUBLE PRECISION   AINVNM
090: *     ..
091: *     .. Local Arrays ..
092:       INTEGER            ISAVE( 3 )
093: *     ..
094: *     .. External Functions ..
095:       LOGICAL            LSAME
096:       EXTERNAL           LSAME
097: *     ..
098: *     .. External Subroutines ..
099:       EXTERNAL           DGTTRS, DLACN2, XERBLA
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( 'DGTCON', -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.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 DLACN2( N, WORK( N+1 ), WORK, IWORK, 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 DGTTRS( '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 DGTTRS( 'Transpose', N, 1, DL, D, DU, DU2, IPIV, WORK,
157:      $                   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 DGTCON
170: *
171:       END
172: