1 *> \brief \b CLA_GBRCOND_C computes the infinity norm condition number of op(A)*inv(diag(c)) for general banded matrices.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CLA_GBRCOND_C + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cla_gbrcond_c.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cla_gbrcond_c.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cla_gbrcond_c.f">
21 * REAL FUNCTION CLA_GBRCOND_C( TRANS, N, KL, KU, AB, LDAB, AFB,
22 * LDAFB, IPIV, C, CAPPLY, INFO, WORK,
25 * .. Scalar Arguments ..
28 * INTEGER N, KL, KU, KD, KE, LDAB, LDAFB, INFO
30 * .. Array Arguments ..
32 * COMPLEX AB( LDAB, * ), AFB( LDAFB, * ), WORK( * )
33 * REAL C( * ), RWORK( * )
42 *> CLA_GBRCOND_C Computes the infinity norm condition number of
43 *> op(A) * inv(diag(C)) where C is a REAL vector.
51 *> TRANS is CHARACTER*1
52 *> Specifies the form of the system of equations:
53 *> = 'N': A * X = B (No transpose)
54 *> = 'T': A**T * X = B (Transpose)
55 *> = 'C': A**H * X = B (Conjugate Transpose = Transpose)
61 *> The number of linear equations, i.e., the order of the
68 *> The number of subdiagonals within the band of A. KL >= 0.
74 *> The number of superdiagonals within the band of A. KU >= 0.
79 *> AB is COMPLEX array, dimension (LDAB,N)
80 *> On entry, the matrix A in band storage, in rows 1 to KL+KU+1.
81 *> The j-th column of A is stored in the j-th column of the
82 *> array AB as follows:
83 *> AB(KU+1+i-j,j) = A(i,j) for max(1,j-KU)<=i<=min(N,j+kl)
89 *> The leading dimension of the array AB. LDAB >= KL+KU+1.
94 *> AFB is COMPLEX array, dimension (LDAFB,N)
95 *> Details of the LU factorization of the band matrix A, as
96 *> computed by CGBTRF. U is stored as an upper triangular
97 *> band matrix with KL+KU superdiagonals in rows 1 to KL+KU+1,
98 *> and the multipliers used during the factorization are stored
99 *> in rows KL+KU+2 to 2*KL+KU+1.
105 *> The leading dimension of the array AFB. LDAFB >= 2*KL+KU+1.
110 *> IPIV is INTEGER array, dimension (N)
111 *> The pivot indices from the factorization A = P*L*U
112 *> as computed by CGBTRF; row i of the matrix was interchanged
118 *> C is REAL array, dimension (N)
119 *> The vector C in the formula op(A) * inv(diag(C)).
125 *> If .TRUE. then access the vector C in the formula above.
131 *> = 0: Successful exit.
132 *> i > 0: The ith argument is invalid.
137 *> WORK is COMPLEX array, dimension (2*N).
143 *> RWORK is REAL array, dimension (N).
150 *> \author Univ. of Tennessee
151 *> \author Univ. of California Berkeley
152 *> \author Univ. of Colorado Denver
155 *> \date September 2012
157 *> \ingroup complexGBcomputational
159 * =====================================================================
160 REAL FUNCTION CLA_GBRCOND_C( TRANS, N, KL, KU, AB, LDAB, AFB,
161 $ LDAFB, IPIV, C, CAPPLY, INFO, WORK,
164 * -- LAPACK computational routine (version 3.4.2) --
165 * -- LAPACK is a software package provided by Univ. of Tennessee, --
166 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
169 * .. Scalar Arguments ..
172 INTEGER N, KL, KU, KD, KE, LDAB, LDAFB, INFO
174 * .. Array Arguments ..
176 COMPLEX AB( LDAB, * ), AFB( LDAFB, * ), WORK( * )
177 REAL C( * ), RWORK( * )
180 * =====================================================================
182 * .. Local Scalars ..
185 REAL AINVNM, ANORM, TMP
191 * .. External Functions ..
195 * .. External Subroutines ..
196 EXTERNAL CLACN2, CGBTRS, XERBLA
198 * .. Intrinsic Functions ..
201 * .. Statement Functions ..
204 * .. Statement Function Definitions ..
205 CABS1( ZDUM ) = ABS( REAL( ZDUM ) ) + ABS( AIMAG( ZDUM ) )
207 * .. Executable Statements ..
208 CLA_GBRCOND_C = 0.0E+0
211 NOTRANS = LSAME( TRANS, 'N' )
212 IF ( .NOT. NOTRANS .AND. .NOT. LSAME( TRANS, 'T' ) .AND. .NOT.
213 $ LSAME( TRANS, 'C' ) ) THEN
215 ELSE IF( N.LT.0 ) THEN
217 ELSE IF( KL.LT.0 .OR. KL.GT.N-1 ) THEN
219 ELSE IF( KU.LT.0 .OR. KU.GT.N-1 ) THEN
221 ELSE IF( LDAB.LT.KL+KU+1 ) THEN
223 ELSE IF( LDAFB.LT.2*KL+KU+1 ) THEN
227 CALL XERBLA( 'CLA_GBRCOND_C', -INFO )
231 * Compute norm of op(A)*op2(C).
240 DO J = MAX( I-KL, 1 ), MIN( I+KU, N )
241 TMP = TMP + CABS1( AB( KD+I-J, J ) ) / C( J )
244 DO J = MAX( I-KL, 1 ), MIN( I+KU, N )
245 TMP = TMP + CABS1( AB( KD+I-J, J ) )
249 ANORM = MAX( ANORM, TMP )
255 DO J = MAX( I-KL, 1 ), MIN( I+KU, N )
256 TMP = TMP + CABS1( AB( KE-I+J, I ) ) / C( J )
259 DO J = MAX( I-KL, 1 ), MIN( I+KU, N )
260 TMP = TMP + CABS1( AB( KE-I+J, I ) )
264 ANORM = MAX( ANORM, TMP )
268 * Quick return if possible.
271 CLA_GBRCOND_C = 1.0E+0
273 ELSE IF( ANORM .EQ. 0.0E+0 ) THEN
277 * Estimate the norm of inv(op(A)).
283 CALL CLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
290 WORK( I ) = WORK( I ) * RWORK( I )
294 CALL CGBTRS( 'No transpose', N, KL, KU, 1, AFB, LDAFB,
295 $ IPIV, WORK, N, INFO )
297 CALL CGBTRS( 'Conjugate transpose', N, KL, KU, 1, AFB,
298 $ LDAFB, IPIV, WORK, N, INFO )
301 * Multiply by inv(C).
305 WORK( I ) = WORK( I ) * C( I )
310 * Multiply by inv(C**H).
314 WORK( I ) = WORK( I ) * C( I )
319 CALL CGBTRS( 'Conjugate transpose', N, KL, KU, 1, AFB,
320 $ LDAFB, IPIV, WORK, N, INFO )
322 CALL CGBTRS( 'No transpose', N, KL, KU, 1, AFB, LDAFB,
323 $ IPIV, WORK, N, INFO )
329 WORK( I ) = WORK( I ) * RWORK( I )
335 * Compute the estimate of the reciprocal condition number.
337 IF( AINVNM .NE. 0.0E+0 )
338 $ CLA_GBRCOND_C = 1.0E+0 / AINVNM