3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download DGBCON + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dgbcon.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dgbcon.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgbcon.f">
21 * SUBROUTINE DGBCON( NORM, N, KL, KU, AB, LDAB, IPIV, ANORM, RCOND,
24 * .. Scalar Arguments ..
26 * INTEGER INFO, KL, KU, LDAB, N
27 * DOUBLE PRECISION ANORM, RCOND
29 * .. Array Arguments ..
30 * INTEGER IPIV( * ), IWORK( * )
31 * DOUBLE PRECISION AB( LDAB, * ), WORK( * )
40 *> DGBCON estimates the reciprocal of the condition number of a real
41 *> general band matrix A, in either the 1-norm or the infinity-norm,
42 *> using the LU factorization computed by DGBTRF.
44 *> An estimate is obtained for norm(inv(A)), and the reciprocal of the
45 *> condition number is computed as
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.
64 *> The order of the matrix A. N >= 0.
70 *> The number of subdiagonals within the band of A. KL >= 0.
76 *> The number of superdiagonals within the band of A. KU >= 0.
81 *> AB is DOUBLE PRECISION array, dimension (LDAB,N)
82 *> Details of the LU factorization of the band matrix A, as
83 *> computed by DGBTRF. U is stored as an upper triangular band
84 *> matrix with KL+KU superdiagonals in rows 1 to KL+KU+1, and
85 *> the multipliers used during the factorization are stored in
86 *> rows KL+KU+2 to 2*KL+KU+1.
92 *> The leading dimension of the array AB. LDAB >= 2*KL+KU+1.
97 *> IPIV is INTEGER array, dimension (N)
98 *> The pivot indices; for 1 <= i <= N, row i of the matrix was
99 *> interchanged with row IPIV(i).
104 *> ANORM is DOUBLE PRECISION
105 *> If NORM = '1' or 'O', the 1-norm of the original matrix A.
106 *> If NORM = 'I', the infinity-norm of the original matrix A.
111 *> RCOND is DOUBLE PRECISION
112 *> The reciprocal of the condition number of the matrix A,
113 *> computed as RCOND = 1/(norm(A) * norm(inv(A))).
118 *> WORK is DOUBLE PRECISION array, dimension (3*N)
123 *> IWORK is INTEGER array, dimension (N)
129 *> = 0: successful exit
130 *> < 0: if INFO = -i, the i-th argument had an illegal value
136 *> \author Univ. of Tennessee
137 *> \author Univ. of California Berkeley
138 *> \author Univ. of Colorado Denver
141 *> \date November 2011
143 *> \ingroup doubleGBcomputational
145 * =====================================================================
146 SUBROUTINE DGBCON( NORM, N, KL, KU, AB, LDAB, IPIV, ANORM, RCOND,
147 $ WORK, IWORK, INFO )
149 * -- LAPACK computational routine (version 3.4.0) --
150 * -- LAPACK is a software package provided by Univ. of Tennessee, --
151 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
154 * .. Scalar Arguments ..
156 INTEGER INFO, KL, KU, LDAB, N
157 DOUBLE PRECISION ANORM, RCOND
159 * .. Array Arguments ..
160 INTEGER IPIV( * ), IWORK( * )
161 DOUBLE PRECISION AB( LDAB, * ), WORK( * )
164 * =====================================================================
167 DOUBLE PRECISION ONE, ZERO
168 PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
170 * .. Local Scalars ..
171 LOGICAL LNOTI, ONENRM
173 INTEGER IX, J, JP, KASE, KASE1, KD, LM
174 DOUBLE PRECISION AINVNM, SCALE, SMLNUM, T
179 * .. External Functions ..
182 DOUBLE PRECISION DDOT, DLAMCH
183 EXTERNAL LSAME, IDAMAX, DDOT, DLAMCH
185 * .. External Subroutines ..
186 EXTERNAL DAXPY, DLACN2, DLATBS, DRSCL, XERBLA
188 * .. Intrinsic Functions ..
191 * .. Executable Statements ..
193 * Test the input parameters.
196 ONENRM = NORM.EQ.'1' .OR. LSAME( NORM, 'O' )
197 IF( .NOT.ONENRM .AND. .NOT.LSAME( NORM, 'I' ) ) THEN
199 ELSE IF( N.LT.0 ) THEN
201 ELSE IF( KL.LT.0 ) THEN
203 ELSE IF( KU.LT.0 ) THEN
205 ELSE IF( LDAB.LT.2*KL+KU+1 ) THEN
207 ELSE IF( ANORM.LT.ZERO ) THEN
211 CALL XERBLA( 'DGBCON', -INFO )
215 * Quick return if possible
221 ELSE IF( ANORM.EQ.ZERO ) THEN
225 SMLNUM = DLAMCH( 'Safe minimum' )
227 * Estimate the norm of inv(A).
240 CALL DLACN2( N, WORK( N+1 ), WORK, IWORK, AINVNM, KASE, ISAVE )
242 IF( KASE.EQ.KASE1 ) THEN
244 * Multiply by inv(L).
252 WORK( JP ) = WORK( J )
255 CALL DAXPY( LM, -T, AB( KD+1, J ), 1, WORK( J+1 ), 1 )
259 * Multiply by inv(U).
261 CALL DLATBS( 'Upper', 'No transpose', 'Non-unit', NORMIN, N,
262 $ KL+KU, AB, LDAB, WORK, SCALE, WORK( 2*N+1 ),
266 * Multiply by inv(U**T).
268 CALL DLATBS( 'Upper', 'Transpose', 'Non-unit', NORMIN, N,
269 $ KL+KU, AB, LDAB, WORK, SCALE, WORK( 2*N+1 ),
272 * Multiply by inv(L**T).
275 DO 30 J = N - 1, 1, -1
277 WORK( J ) = WORK( J ) - DDOT( LM, AB( KD+1, J ), 1,
282 WORK( JP ) = WORK( J )
289 * Divide X by 1/SCALE if doing so will not cause overflow.
292 IF( SCALE.NE.ONE ) THEN
293 IX = IDAMAX( N, WORK, 1 )
294 IF( SCALE.LT.ABS( WORK( IX ) )*SMLNUM .OR. SCALE.EQ.ZERO )
296 CALL DRSCL( N, SCALE, WORK, 1 )
301 * Compute the estimate of the reciprocal condition number.
304 $ RCOND = ( ONE / AINVNM ) / ANORM