1 SUBROUTINE ZTRCON( NORM, UPLO, DIAG, N, A, LDA, RCOND, WORK,
2 $ RWORK, 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 ZLACN2 in place of ZLACON, 10 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 DOUBLE PRECISION RWORK( * )
18 COMPLEX*16 A( LDA, * ), WORK( * )
19 * ..
20 *
21 * Purpose
22 * =======
23 *
24 * ZTRCON 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) COMPLEX*16 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) COMPLEX*16 array, dimension (2*N)
70 *
71 * RWORK (workspace) DOUBLE PRECISION 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 COMPLEX*16 ZDUM
89 * ..
90 * .. Local Arrays ..
91 INTEGER ISAVE( 3 )
92 * ..
93 * .. External Functions ..
94 LOGICAL LSAME
95 INTEGER IZAMAX
96 DOUBLE PRECISION DLAMCH, ZLANTR
97 EXTERNAL LSAME, IZAMAX, DLAMCH, ZLANTR
98 * ..
99 * .. External Subroutines ..
100 EXTERNAL XERBLA, ZDRSCL, ZLACN2, ZLATRS
101 * ..
102 * .. Intrinsic Functions ..
103 INTRINSIC ABS, DBLE, DIMAG, MAX
104 * ..
105 * .. Statement Functions ..
106 DOUBLE PRECISION CABS1
107 * ..
108 * .. Statement Function definitions ..
109 CABS1( ZDUM ) = ABS( DBLE( ZDUM ) ) + ABS( DIMAG( ZDUM ) )
110 * ..
111 * .. Executable Statements ..
112 *
113 * Test the input parameters.
114 *
115 INFO = 0
116 UPPER = LSAME( UPLO, 'U' )
117 ONENRM = NORM.EQ.'1' .OR. LSAME( NORM, 'O' )
118 NOUNIT = LSAME( DIAG, 'N' )
119 *
120 IF( .NOT.ONENRM .AND. .NOT.LSAME( NORM, 'I' ) ) THEN
121 INFO = -1
122 ELSE IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
123 INFO = -2
124 ELSE IF( .NOT.NOUNIT .AND. .NOT.LSAME( DIAG, 'U' ) ) THEN
125 INFO = -3
126 ELSE IF( N.LT.0 ) THEN
127 INFO = -4
128 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
129 INFO = -6
130 END IF
131 IF( INFO.NE.0 ) THEN
132 CALL XERBLA( 'ZTRCON', -INFO )
133 RETURN
134 END IF
135 *
136 * Quick return if possible
137 *
138 IF( N.EQ.0 ) THEN
139 RCOND = ONE
140 RETURN
141 END IF
142 *
143 RCOND = ZERO
144 SMLNUM = DLAMCH( 'Safe minimum' )*DBLE( MAX( 1, N ) )
145 *
146 * Compute the norm of the triangular matrix A.
147 *
148 ANORM = ZLANTR( NORM, UPLO, DIAG, N, N, A, LDA, RWORK )
149 *
150 * Continue only if ANORM > 0.
151 *
152 IF( ANORM.GT.ZERO ) THEN
153 *
154 * Estimate the norm of the inverse of A.
155 *
156 AINVNM = ZERO
157 NORMIN = 'N'
158 IF( ONENRM ) THEN
159 KASE1 = 1
160 ELSE
161 KASE1 = 2
162 END IF
163 KASE = 0
164 10 CONTINUE
165 CALL ZLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
166 IF( KASE.NE.0 ) THEN
167 IF( KASE.EQ.KASE1 ) THEN
168 *
169 * Multiply by inv(A).
170 *
171 CALL ZLATRS( UPLO, 'No transpose', DIAG, NORMIN, N, A,
172 $ LDA, WORK, SCALE, RWORK, INFO )
173 ELSE
174 *
175 * Multiply by inv(A**H).
176 *
177 CALL ZLATRS( UPLO, 'Conjugate transpose', DIAG, NORMIN,
178 $ N, A, LDA, WORK, SCALE, RWORK, INFO )
179 END IF
180 NORMIN = 'Y'
181 *
182 * Multiply by 1/SCALE if doing so will not cause overflow.
183 *
184 IF( SCALE.NE.ONE ) THEN
185 IX = IZAMAX( N, WORK, 1 )
186 XNORM = CABS1( WORK( IX ) )
187 IF( SCALE.LT.XNORM*SMLNUM .OR. SCALE.EQ.ZERO )
188 $ GO TO 20
189 CALL ZDRSCL( N, SCALE, WORK, 1 )
190 END IF
191 GO TO 10
192 END IF
193 *
194 * Compute the estimate of the reciprocal condition number.
195 *
196 IF( AINVNM.NE.ZERO )
197 $ RCOND = ( ONE / ANORM ) / AINVNM
198 END IF
199 *
200 20 CONTINUE
201 RETURN
202 *
203 * End of ZTRCON
204 *
205 END
2 $ RWORK, 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 ZLACN2 in place of ZLACON, 10 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 DOUBLE PRECISION RWORK( * )
18 COMPLEX*16 A( LDA, * ), WORK( * )
19 * ..
20 *
21 * Purpose
22 * =======
23 *
24 * ZTRCON 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) COMPLEX*16 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) COMPLEX*16 array, dimension (2*N)
70 *
71 * RWORK (workspace) DOUBLE PRECISION 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 COMPLEX*16 ZDUM
89 * ..
90 * .. Local Arrays ..
91 INTEGER ISAVE( 3 )
92 * ..
93 * .. External Functions ..
94 LOGICAL LSAME
95 INTEGER IZAMAX
96 DOUBLE PRECISION DLAMCH, ZLANTR
97 EXTERNAL LSAME, IZAMAX, DLAMCH, ZLANTR
98 * ..
99 * .. External Subroutines ..
100 EXTERNAL XERBLA, ZDRSCL, ZLACN2, ZLATRS
101 * ..
102 * .. Intrinsic Functions ..
103 INTRINSIC ABS, DBLE, DIMAG, MAX
104 * ..
105 * .. Statement Functions ..
106 DOUBLE PRECISION CABS1
107 * ..
108 * .. Statement Function definitions ..
109 CABS1( ZDUM ) = ABS( DBLE( ZDUM ) ) + ABS( DIMAG( ZDUM ) )
110 * ..
111 * .. Executable Statements ..
112 *
113 * Test the input parameters.
114 *
115 INFO = 0
116 UPPER = LSAME( UPLO, 'U' )
117 ONENRM = NORM.EQ.'1' .OR. LSAME( NORM, 'O' )
118 NOUNIT = LSAME( DIAG, 'N' )
119 *
120 IF( .NOT.ONENRM .AND. .NOT.LSAME( NORM, 'I' ) ) THEN
121 INFO = -1
122 ELSE IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
123 INFO = -2
124 ELSE IF( .NOT.NOUNIT .AND. .NOT.LSAME( DIAG, 'U' ) ) THEN
125 INFO = -3
126 ELSE IF( N.LT.0 ) THEN
127 INFO = -4
128 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
129 INFO = -6
130 END IF
131 IF( INFO.NE.0 ) THEN
132 CALL XERBLA( 'ZTRCON', -INFO )
133 RETURN
134 END IF
135 *
136 * Quick return if possible
137 *
138 IF( N.EQ.0 ) THEN
139 RCOND = ONE
140 RETURN
141 END IF
142 *
143 RCOND = ZERO
144 SMLNUM = DLAMCH( 'Safe minimum' )*DBLE( MAX( 1, N ) )
145 *
146 * Compute the norm of the triangular matrix A.
147 *
148 ANORM = ZLANTR( NORM, UPLO, DIAG, N, N, A, LDA, RWORK )
149 *
150 * Continue only if ANORM > 0.
151 *
152 IF( ANORM.GT.ZERO ) THEN
153 *
154 * Estimate the norm of the inverse of A.
155 *
156 AINVNM = ZERO
157 NORMIN = 'N'
158 IF( ONENRM ) THEN
159 KASE1 = 1
160 ELSE
161 KASE1 = 2
162 END IF
163 KASE = 0
164 10 CONTINUE
165 CALL ZLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
166 IF( KASE.NE.0 ) THEN
167 IF( KASE.EQ.KASE1 ) THEN
168 *
169 * Multiply by inv(A).
170 *
171 CALL ZLATRS( UPLO, 'No transpose', DIAG, NORMIN, N, A,
172 $ LDA, WORK, SCALE, RWORK, INFO )
173 ELSE
174 *
175 * Multiply by inv(A**H).
176 *
177 CALL ZLATRS( UPLO, 'Conjugate transpose', DIAG, NORMIN,
178 $ N, A, LDA, WORK, SCALE, RWORK, INFO )
179 END IF
180 NORMIN = 'Y'
181 *
182 * Multiply by 1/SCALE if doing so will not cause overflow.
183 *
184 IF( SCALE.NE.ONE ) THEN
185 IX = IZAMAX( N, WORK, 1 )
186 XNORM = CABS1( WORK( IX ) )
187 IF( SCALE.LT.XNORM*SMLNUM .OR. SCALE.EQ.ZERO )
188 $ GO TO 20
189 CALL ZDRSCL( N, SCALE, WORK, 1 )
190 END IF
191 GO TO 10
192 END IF
193 *
194 * Compute the estimate of the reciprocal condition number.
195 *
196 IF( AINVNM.NE.ZERO )
197 $ RCOND = ( ONE / ANORM ) / AINVNM
198 END IF
199 *
200 20 CONTINUE
201 RETURN
202 *
203 * End of ZTRCON
204 *
205 END