1 SUBROUTINE DTRCON( NORM, UPLO, DIAG, N, A, LDA, RCOND, WORK,
2 $ IWORK, INFO )
3 *
4 * -- LAPACK routine (version 3.2) --
5 * -- LAPACK is a software package provided by Univ. of Tennessee, --
6 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
7 * November 2006
8 *
9 * Modified to call DLACN2 in place of DLACON, 5 Feb 03, SJH.
10 *
11 * .. Scalar Arguments ..
12 CHARACTER DIAG, NORM, UPLO
13 INTEGER INFO, LDA, N
14 DOUBLE PRECISION RCOND
15 * ..
16 * .. Array Arguments ..
17 INTEGER IWORK( * )
18 DOUBLE PRECISION A( LDA, * ), WORK( * )
19 * ..
20 *
21 * Purpose
22 * =======
23 *
24 * DTRCON estimates the reciprocal of the condition number of a
25 * triangular matrix A, in either the 1-norm or the infinity-norm.
26 *
27 * The norm of A is computed and an estimate is obtained for
28 * norm(inv(A)), then the reciprocal of the condition number is
29 * computed as
30 * RCOND = 1 / ( norm(A) * norm(inv(A)) ).
31 *
32 * Arguments
33 * =========
34 *
35 * NORM (input) CHARACTER*1
36 * Specifies whether the 1-norm condition number or the
37 * infinity-norm condition number is required:
38 * = '1' or 'O': 1-norm;
39 * = 'I': Infinity-norm.
40 *
41 * UPLO (input) CHARACTER*1
42 * = 'U': A is upper triangular;
43 * = 'L': A is lower triangular.
44 *
45 * DIAG (input) CHARACTER*1
46 * = 'N': A is non-unit triangular;
47 * = 'U': A is unit triangular.
48 *
49 * N (input) INTEGER
50 * The order of the matrix A. N >= 0.
51 *
52 * A (input) DOUBLE PRECISION array, dimension (LDA,N)
53 * The triangular matrix A. If UPLO = 'U', the leading N-by-N
54 * upper triangular part of the array A contains the upper
55 * triangular matrix, and the strictly lower triangular part of
56 * A is not referenced. If UPLO = 'L', the leading N-by-N lower
57 * triangular part of the array A contains the lower triangular
58 * matrix, and the strictly upper triangular part of A is not
59 * referenced. If DIAG = 'U', the diagonal elements of A are
60 * also not referenced and are assumed to be 1.
61 *
62 * LDA (input) INTEGER
63 * The leading dimension of the array A. LDA >= max(1,N).
64 *
65 * RCOND (output) DOUBLE PRECISION
66 * The reciprocal of the condition number of the matrix A,
67 * computed as RCOND = 1/(norm(A) * norm(inv(A))).
68 *
69 * WORK (workspace) DOUBLE PRECISION array, dimension (3*N)
70 *
71 * IWORK (workspace) INTEGER array, dimension (N)
72 *
73 * INFO (output) INTEGER
74 * = 0: successful exit
75 * < 0: if INFO = -i, the i-th argument had an illegal value
76 *
77 * =====================================================================
78 *
79 * .. Parameters ..
80 DOUBLE PRECISION ONE, ZERO
81 PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
82 * ..
83 * .. Local Scalars ..
84 LOGICAL NOUNIT, ONENRM, UPPER
85 CHARACTER NORMIN
86 INTEGER IX, KASE, KASE1
87 DOUBLE PRECISION AINVNM, ANORM, SCALE, SMLNUM, XNORM
88 * ..
89 * .. Local Arrays ..
90 INTEGER ISAVE( 3 )
91 * ..
92 * .. External Functions ..
93 LOGICAL LSAME
94 INTEGER IDAMAX
95 DOUBLE PRECISION DLAMCH, DLANTR
96 EXTERNAL LSAME, IDAMAX, DLAMCH, DLANTR
97 * ..
98 * .. External Subroutines ..
99 EXTERNAL DLACN2, DLATRS, DRSCL, XERBLA
100 * ..
101 * .. Intrinsic Functions ..
102 INTRINSIC ABS, DBLE, MAX
103 * ..
104 * .. Executable Statements ..
105 *
106 * Test the input parameters.
107 *
108 INFO = 0
109 UPPER = LSAME( UPLO, 'U' )
110 ONENRM = NORM.EQ.'1' .OR. LSAME( NORM, 'O' )
111 NOUNIT = LSAME( DIAG, 'N' )
112 *
113 IF( .NOT.ONENRM .AND. .NOT.LSAME( NORM, 'I' ) ) THEN
114 INFO = -1
115 ELSE IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
116 INFO = -2
117 ELSE IF( .NOT.NOUNIT .AND. .NOT.LSAME( DIAG, 'U' ) ) THEN
118 INFO = -3
119 ELSE IF( N.LT.0 ) THEN
120 INFO = -4
121 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
122 INFO = -6
123 END IF
124 IF( INFO.NE.0 ) THEN
125 CALL XERBLA( 'DTRCON', -INFO )
126 RETURN
127 END IF
128 *
129 * Quick return if possible
130 *
131 IF( N.EQ.0 ) THEN
132 RCOND = ONE
133 RETURN
134 END IF
135 *
136 RCOND = ZERO
137 SMLNUM = DLAMCH( 'Safe minimum' )*DBLE( MAX( 1, N ) )
138 *
139 * Compute the norm of the triangular matrix A.
140 *
141 ANORM = DLANTR( NORM, UPLO, DIAG, N, N, A, LDA, WORK )
142 *
143 * Continue only if ANORM > 0.
144 *
145 IF( ANORM.GT.ZERO ) THEN
146 *
147 * Estimate the norm of the inverse of A.
148 *
149 AINVNM = ZERO
150 NORMIN = 'N'
151 IF( ONENRM ) THEN
152 KASE1 = 1
153 ELSE
154 KASE1 = 2
155 END IF
156 KASE = 0
157 10 CONTINUE
158 CALL DLACN2( N, WORK( N+1 ), WORK, IWORK, AINVNM, KASE, ISAVE )
159 IF( KASE.NE.0 ) THEN
160 IF( KASE.EQ.KASE1 ) THEN
161 *
162 * Multiply by inv(A).
163 *
164 CALL DLATRS( UPLO, 'No transpose', DIAG, NORMIN, N, A,
165 $ LDA, WORK, SCALE, WORK( 2*N+1 ), INFO )
166 ELSE
167 *
168 * Multiply by inv(A**T).
169 *
170 CALL DLATRS( UPLO, 'Transpose', DIAG, NORMIN, N, A, LDA,
171 $ WORK, SCALE, WORK( 2*N+1 ), INFO )
172 END IF
173 NORMIN = 'Y'
174 *
175 * Multiply by 1/SCALE if doing so will not cause overflow.
176 *
177 IF( SCALE.NE.ONE ) THEN
178 IX = IDAMAX( N, WORK, 1 )
179 XNORM = ABS( WORK( IX ) )
180 IF( SCALE.LT.XNORM*SMLNUM .OR. SCALE.EQ.ZERO )
181 $ GO TO 20
182 CALL DRSCL( 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 / ANORM ) / AINVNM
191 END IF
192 *
193 20 CONTINUE
194 RETURN
195 *
196 * End of DTRCON
197 *
198 END
2 $ IWORK, INFO )
3 *
4 * -- LAPACK routine (version 3.2) --
5 * -- LAPACK is a software package provided by Univ. of Tennessee, --
6 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
7 * November 2006
8 *
9 * Modified to call DLACN2 in place of DLACON, 5 Feb 03, SJH.
10 *
11 * .. Scalar Arguments ..
12 CHARACTER DIAG, NORM, UPLO
13 INTEGER INFO, LDA, N
14 DOUBLE PRECISION RCOND
15 * ..
16 * .. Array Arguments ..
17 INTEGER IWORK( * )
18 DOUBLE PRECISION A( LDA, * ), WORK( * )
19 * ..
20 *
21 * Purpose
22 * =======
23 *
24 * DTRCON estimates the reciprocal of the condition number of a
25 * triangular matrix A, in either the 1-norm or the infinity-norm.
26 *
27 * The norm of A is computed and an estimate is obtained for
28 * norm(inv(A)), then the reciprocal of the condition number is
29 * computed as
30 * RCOND = 1 / ( norm(A) * norm(inv(A)) ).
31 *
32 * Arguments
33 * =========
34 *
35 * NORM (input) CHARACTER*1
36 * Specifies whether the 1-norm condition number or the
37 * infinity-norm condition number is required:
38 * = '1' or 'O': 1-norm;
39 * = 'I': Infinity-norm.
40 *
41 * UPLO (input) CHARACTER*1
42 * = 'U': A is upper triangular;
43 * = 'L': A is lower triangular.
44 *
45 * DIAG (input) CHARACTER*1
46 * = 'N': A is non-unit triangular;
47 * = 'U': A is unit triangular.
48 *
49 * N (input) INTEGER
50 * The order of the matrix A. N >= 0.
51 *
52 * A (input) DOUBLE PRECISION array, dimension (LDA,N)
53 * The triangular matrix A. If UPLO = 'U', the leading N-by-N
54 * upper triangular part of the array A contains the upper
55 * triangular matrix, and the strictly lower triangular part of
56 * A is not referenced. If UPLO = 'L', the leading N-by-N lower
57 * triangular part of the array A contains the lower triangular
58 * matrix, and the strictly upper triangular part of A is not
59 * referenced. If DIAG = 'U', the diagonal elements of A are
60 * also not referenced and are assumed to be 1.
61 *
62 * LDA (input) INTEGER
63 * The leading dimension of the array A. LDA >= max(1,N).
64 *
65 * RCOND (output) DOUBLE PRECISION
66 * The reciprocal of the condition number of the matrix A,
67 * computed as RCOND = 1/(norm(A) * norm(inv(A))).
68 *
69 * WORK (workspace) DOUBLE PRECISION array, dimension (3*N)
70 *
71 * IWORK (workspace) INTEGER array, dimension (N)
72 *
73 * INFO (output) INTEGER
74 * = 0: successful exit
75 * < 0: if INFO = -i, the i-th argument had an illegal value
76 *
77 * =====================================================================
78 *
79 * .. Parameters ..
80 DOUBLE PRECISION ONE, ZERO
81 PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
82 * ..
83 * .. Local Scalars ..
84 LOGICAL NOUNIT, ONENRM, UPPER
85 CHARACTER NORMIN
86 INTEGER IX, KASE, KASE1
87 DOUBLE PRECISION AINVNM, ANORM, SCALE, SMLNUM, XNORM
88 * ..
89 * .. Local Arrays ..
90 INTEGER ISAVE( 3 )
91 * ..
92 * .. External Functions ..
93 LOGICAL LSAME
94 INTEGER IDAMAX
95 DOUBLE PRECISION DLAMCH, DLANTR
96 EXTERNAL LSAME, IDAMAX, DLAMCH, DLANTR
97 * ..
98 * .. External Subroutines ..
99 EXTERNAL DLACN2, DLATRS, DRSCL, XERBLA
100 * ..
101 * .. Intrinsic Functions ..
102 INTRINSIC ABS, DBLE, MAX
103 * ..
104 * .. Executable Statements ..
105 *
106 * Test the input parameters.
107 *
108 INFO = 0
109 UPPER = LSAME( UPLO, 'U' )
110 ONENRM = NORM.EQ.'1' .OR. LSAME( NORM, 'O' )
111 NOUNIT = LSAME( DIAG, 'N' )
112 *
113 IF( .NOT.ONENRM .AND. .NOT.LSAME( NORM, 'I' ) ) THEN
114 INFO = -1
115 ELSE IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
116 INFO = -2
117 ELSE IF( .NOT.NOUNIT .AND. .NOT.LSAME( DIAG, 'U' ) ) THEN
118 INFO = -3
119 ELSE IF( N.LT.0 ) THEN
120 INFO = -4
121 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
122 INFO = -6
123 END IF
124 IF( INFO.NE.0 ) THEN
125 CALL XERBLA( 'DTRCON', -INFO )
126 RETURN
127 END IF
128 *
129 * Quick return if possible
130 *
131 IF( N.EQ.0 ) THEN
132 RCOND = ONE
133 RETURN
134 END IF
135 *
136 RCOND = ZERO
137 SMLNUM = DLAMCH( 'Safe minimum' )*DBLE( MAX( 1, N ) )
138 *
139 * Compute the norm of the triangular matrix A.
140 *
141 ANORM = DLANTR( NORM, UPLO, DIAG, N, N, A, LDA, WORK )
142 *
143 * Continue only if ANORM > 0.
144 *
145 IF( ANORM.GT.ZERO ) THEN
146 *
147 * Estimate the norm of the inverse of A.
148 *
149 AINVNM = ZERO
150 NORMIN = 'N'
151 IF( ONENRM ) THEN
152 KASE1 = 1
153 ELSE
154 KASE1 = 2
155 END IF
156 KASE = 0
157 10 CONTINUE
158 CALL DLACN2( N, WORK( N+1 ), WORK, IWORK, AINVNM, KASE, ISAVE )
159 IF( KASE.NE.0 ) THEN
160 IF( KASE.EQ.KASE1 ) THEN
161 *
162 * Multiply by inv(A).
163 *
164 CALL DLATRS( UPLO, 'No transpose', DIAG, NORMIN, N, A,
165 $ LDA, WORK, SCALE, WORK( 2*N+1 ), INFO )
166 ELSE
167 *
168 * Multiply by inv(A**T).
169 *
170 CALL DLATRS( UPLO, 'Transpose', DIAG, NORMIN, N, A, LDA,
171 $ WORK, SCALE, WORK( 2*N+1 ), INFO )
172 END IF
173 NORMIN = 'Y'
174 *
175 * Multiply by 1/SCALE if doing so will not cause overflow.
176 *
177 IF( SCALE.NE.ONE ) THEN
178 IX = IDAMAX( N, WORK, 1 )
179 XNORM = ABS( WORK( IX ) )
180 IF( SCALE.LT.XNORM*SMLNUM .OR. SCALE.EQ.ZERO )
181 $ GO TO 20
182 CALL DRSCL( 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 / ANORM ) / AINVNM
191 END IF
192 *
193 20 CONTINUE
194 RETURN
195 *
196 * End of DTRCON
197 *
198 END