3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CTBCON + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ctbcon.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ctbcon.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ctbcon.f">
21 * SUBROUTINE CTBCON( NORM, UPLO, DIAG, N, KD, AB, LDAB, RCOND, WORK,
24 * .. Scalar Arguments ..
25 * CHARACTER DIAG, NORM, UPLO
26 * INTEGER INFO, KD, LDAB, N
29 * .. Array Arguments ..
31 * COMPLEX AB( LDAB, * ), WORK( * )
40 *> CTBCON estimates the reciprocal of the condition number of a
41 *> triangular band matrix A, in either the 1-norm or the infinity-norm.
43 *> The norm of A is computed and an estimate is obtained for
44 *> norm(inv(A)), then the reciprocal of the condition number is
46 *> RCOND = 1 / ( norm(A) * norm(inv(A)) ).
54 *> NORM is CHARACTER*1
55 *> Specifies whether the 1-norm condition number or the
56 *> infinity-norm condition number is required:
57 *> = '1' or 'O': 1-norm;
58 *> = 'I': Infinity-norm.
63 *> UPLO is CHARACTER*1
64 *> = 'U': A is upper triangular;
65 *> = 'L': A is lower triangular.
70 *> DIAG is CHARACTER*1
71 *> = 'N': A is non-unit triangular;
72 *> = 'U': A is unit triangular.
78 *> The order of the matrix A. N >= 0.
84 *> The number of superdiagonals or subdiagonals of the
85 *> triangular band matrix A. KD >= 0.
90 *> AB is COMPLEX array, dimension (LDAB,N)
91 *> The upper or lower triangular band matrix A, stored in the
92 *> first kd+1 rows of the array. The j-th column of A is stored
93 *> in the j-th column of the array AB as follows:
94 *> if UPLO = 'U', AB(kd+1+i-j,j) = A(i,j) for max(1,j-kd)<=i<=j;
95 *> if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(n,j+kd).
96 *> If DIAG = 'U', the diagonal elements of A are not referenced
97 *> and are assumed to be 1.
103 *> The leading dimension of the array AB. LDAB >= KD+1.
109 *> The reciprocal of the condition number of the matrix A,
110 *> computed as RCOND = 1/(norm(A) * norm(inv(A))).
115 *> WORK is COMPLEX array, dimension (2*N)
120 *> RWORK is REAL array, dimension (N)
126 *> = 0: successful exit
127 *> < 0: if INFO = -i, the i-th argument had an illegal value
133 *> \author Univ. of Tennessee
134 *> \author Univ. of California Berkeley
135 *> \author Univ. of Colorado Denver
138 *> \date November 2011
140 *> \ingroup complexOTHERcomputational
142 * =====================================================================
143 SUBROUTINE CTBCON( NORM, UPLO, DIAG, N, KD, AB, LDAB, RCOND, WORK,
146 * -- LAPACK computational routine (version 3.4.0) --
147 * -- LAPACK is a software package provided by Univ. of Tennessee, --
148 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
151 * .. Scalar Arguments ..
152 CHARACTER DIAG, NORM, UPLO
153 INTEGER INFO, KD, LDAB, N
156 * .. Array Arguments ..
158 COMPLEX AB( LDAB, * ), WORK( * )
161 * =====================================================================
165 PARAMETER ( ONE = 1.0E+0, ZERO = 0.0E+0 )
167 * .. Local Scalars ..
168 LOGICAL NOUNIT, ONENRM, UPPER
170 INTEGER IX, KASE, KASE1
171 REAL AINVNM, ANORM, SCALE, SMLNUM, XNORM
177 * .. External Functions ..
181 EXTERNAL LSAME, ICAMAX, CLANTB, SLAMCH
183 * .. External Subroutines ..
184 EXTERNAL CLACN2, CLATBS, CSRSCL, XERBLA
186 * .. Intrinsic Functions ..
187 INTRINSIC ABS, AIMAG, MAX, REAL
189 * .. Statement Functions ..
192 * .. Statement Function definitions ..
193 CABS1( ZDUM ) = ABS( REAL( ZDUM ) ) + ABS( AIMAG( ZDUM ) )
195 * .. Executable Statements ..
197 * Test the input parameters.
200 UPPER = LSAME( UPLO, 'U' )
201 ONENRM = NORM.EQ.'1' .OR. LSAME( NORM, 'O' )
202 NOUNIT = LSAME( DIAG, 'N' )
204 IF( .NOT.ONENRM .AND. .NOT.LSAME( NORM, 'I' ) ) THEN
206 ELSE IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
208 ELSE IF( .NOT.NOUNIT .AND. .NOT.LSAME( DIAG, 'U' ) ) THEN
210 ELSE IF( N.LT.0 ) THEN
212 ELSE IF( KD.LT.0 ) THEN
214 ELSE IF( LDAB.LT.KD+1 ) THEN
218 CALL XERBLA( 'CTBCON', -INFO )
222 * Quick return if possible
230 SMLNUM = SLAMCH( 'Safe minimum' )*REAL( MAX( N, 1 ) )
232 * Compute the 1-norm of the triangular matrix A or A**H.
234 ANORM = CLANTB( NORM, UPLO, DIAG, N, KD, AB, LDAB, RWORK )
236 * Continue only if ANORM > 0.
238 IF( ANORM.GT.ZERO ) THEN
240 * Estimate the 1-norm of the inverse of A.
251 CALL CLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
253 IF( KASE.EQ.KASE1 ) THEN
255 * Multiply by inv(A).
257 CALL CLATBS( UPLO, 'No transpose', DIAG, NORMIN, N, KD,
258 $ AB, LDAB, WORK, SCALE, RWORK, INFO )
261 * Multiply by inv(A**H).
263 CALL CLATBS( UPLO, 'Conjugate transpose', DIAG, NORMIN,
264 $ N, KD, AB, LDAB, WORK, SCALE, RWORK, INFO )
268 * Multiply by 1/SCALE if doing so will not cause overflow.
270 IF( SCALE.NE.ONE ) THEN
271 IX = ICAMAX( N, WORK, 1 )
272 XNORM = CABS1( WORK( IX ) )
273 IF( SCALE.LT.XNORM*SMLNUM .OR. SCALE.EQ.ZERO )
275 CALL CSRSCL( N, SCALE, WORK, 1 )
280 * Compute the estimate of the reciprocal condition number.
283 $ RCOND = ( ONE / ANORM ) / AINVNM