1 *> \brief \b CLA_GBRCOND_X computes the infinity norm condition number of op(A)*diag(x) for general banded matrices.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CLA_GBRCOND_X + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cla_gbrcond_x.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cla_gbrcond_x.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cla_gbrcond_x.f">
21 * REAL FUNCTION CLA_GBRCOND_X( TRANS, N, KL, KU, AB, LDAB, AFB,
22 * LDAFB, IPIV, X, INFO, WORK, RWORK )
24 * .. Scalar Arguments ..
26 * INTEGER N, KL, KU, KD, KE, LDAB, LDAFB, INFO
28 * .. Array Arguments ..
30 * COMPLEX AB( LDAB, * ), AFB( LDAFB, * ), WORK( * ),
41 *> CLA_GBRCOND_X Computes the infinity norm condition number of
42 *> op(A) * diag(X) where X is a COMPLEX vector.
50 *> TRANS is CHARACTER*1
51 *> Specifies the form of the system of equations:
52 *> = 'N': A * X = B (No transpose)
53 *> = 'T': A**T * X = B (Transpose)
54 *> = 'C': A**H * X = B (Conjugate Transpose = Transpose)
60 *> The number of linear equations, i.e., the order of the
67 *> The number of subdiagonals within the band of A. KL >= 0.
73 *> The number of superdiagonals within the band of A. KU >= 0.
78 *> AB is COMPLEX array, dimension (LDAB,N)
79 *> On entry, the matrix A in band storage, in rows 1 to KL+KU+1.
80 *> The j-th column of A is stored in the j-th column of the
81 *> array AB as follows:
82 *> AB(KU+1+i-j,j) = A(i,j) for max(1,j-KU)<=i<=min(N,j+kl)
88 *> The leading dimension of the array AB. LDAB >= KL+KU+1.
93 *> AFB is COMPLEX array, dimension (LDAFB,N)
94 *> Details of the LU factorization of the band matrix A, as
95 *> computed by CGBTRF. U is stored as an upper triangular
96 *> band matrix with KL+KU superdiagonals in rows 1 to KL+KU+1,
97 *> and the multipliers used during the factorization are stored
98 *> in rows KL+KU+2 to 2*KL+KU+1.
104 *> The leading dimension of the array AFB. LDAFB >= 2*KL+KU+1.
109 *> IPIV is INTEGER array, dimension (N)
110 *> The pivot indices from the factorization A = P*L*U
111 *> as computed by CGBTRF; row i of the matrix was interchanged
117 *> X is COMPLEX array, dimension (N)
118 *> The vector X in the formula op(A) * diag(X).
124 *> = 0: Successful exit.
125 *> i > 0: The ith argument is invalid.
130 *> WORK is COMPLEX array, dimension (2*N).
136 *> RWORK is REAL array, dimension (N).
143 *> \author Univ. of Tennessee
144 *> \author Univ. of California Berkeley
145 *> \author Univ. of Colorado Denver
148 *> \date September 2012
150 *> \ingroup complexGBcomputational
152 * =====================================================================
153 REAL FUNCTION CLA_GBRCOND_X( TRANS, N, KL, KU, AB, LDAB, AFB,
154 $ LDAFB, IPIV, X, INFO, WORK, RWORK )
156 * -- LAPACK computational routine (version 3.4.2) --
157 * -- LAPACK is a software package provided by Univ. of Tennessee, --
158 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
161 * .. Scalar Arguments ..
163 INTEGER N, KL, KU, KD, KE, LDAB, LDAFB, INFO
165 * .. Array Arguments ..
167 COMPLEX AB( LDAB, * ), AFB( LDAFB, * ), WORK( * ),
172 * =====================================================================
174 * .. Local Scalars ..
177 REAL AINVNM, ANORM, TMP
183 * .. External Functions ..
187 * .. External Subroutines ..
188 EXTERNAL CLACN2, CGBTRS, XERBLA
190 * .. Intrinsic Functions ..
193 * .. Statement Functions ..
196 * .. Statement Function Definitions ..
197 CABS1( ZDUM ) = ABS( REAL( ZDUM ) ) + ABS( AIMAG( ZDUM ) )
199 * .. Executable Statements ..
201 CLA_GBRCOND_X = 0.0E+0
204 NOTRANS = LSAME( TRANS, 'N' )
205 IF ( .NOT. NOTRANS .AND. .NOT. LSAME(TRANS, 'T') .AND. .NOT.
206 $ LSAME( TRANS, 'C' ) ) THEN
208 ELSE IF( N.LT.0 ) THEN
210 ELSE IF( KL.LT.0 .OR. KL.GT.N-1 ) THEN
212 ELSE IF( KU.LT.0 .OR. KU.GT.N-1 ) THEN
214 ELSE IF( LDAB.LT.KL+KU+1 ) THEN
216 ELSE IF( LDAFB.LT.2*KL+KU+1 ) THEN
220 CALL XERBLA( 'CLA_GBRCOND_X', -INFO )
224 * Compute norm of op(A)*op2(C).
232 DO J = MAX( I-KL, 1 ), MIN( I+KU, N )
233 TMP = TMP + CABS1( AB( KD+I-J, J) * X( J ) )
236 ANORM = MAX( ANORM, TMP )
241 DO J = MAX( I-KL, 1 ), MIN( I+KU, N )
242 TMP = TMP + CABS1( AB( KE-I+J, I ) * X( J ) )
245 ANORM = MAX( ANORM, TMP )
249 * Quick return if possible.
252 CLA_GBRCOND_X = 1.0E+0
254 ELSE IF( ANORM .EQ. 0.0E+0 ) THEN
258 * Estimate the norm of inv(op(A)).
264 CALL CLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
271 WORK( I ) = WORK( I ) * RWORK( I )
275 CALL CGBTRS( 'No transpose', N, KL, KU, 1, AFB, LDAFB,
276 $ IPIV, WORK, N, INFO )
278 CALL CGBTRS( 'Conjugate transpose', N, KL, KU, 1, AFB,
279 $ LDAFB, IPIV, WORK, N, INFO )
282 * Multiply by inv(X).
285 WORK( I ) = WORK( I ) / X( I )
289 * Multiply by inv(X**H).
292 WORK( I ) = WORK( I ) / X( I )
296 CALL CGBTRS( 'Conjugate transpose', N, KL, KU, 1, AFB,
297 $ LDAFB, IPIV, WORK, N, INFO )
299 CALL CGBTRS( 'No transpose', N, KL, KU, 1, AFB, LDAFB,
300 $ IPIV, WORK, N, INFO )
306 WORK( I ) = WORK( I ) * RWORK( I )
312 * Compute the estimate of the reciprocal condition number.
314 IF( AINVNM .NE. 0.0E+0 )
315 $ CLA_GBRCOND_X = 1.0E+0 / AINVNM