3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download SGECON + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sgecon.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sgecon.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sgecon.f">
21 * SUBROUTINE SGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
24 * .. Scalar Arguments ..
26 * INTEGER INFO, LDA, N
29 * .. Array Arguments ..
31 * REAL A( LDA, * ), WORK( * )
40 *> SGECON estimates the reciprocal of the condition number of a general
41 *> real matrix A, in either the 1-norm or the infinity-norm, using
42 *> the LU factorization computed by SGETRF.
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.
69 *> A is REAL array, dimension (LDA,N)
70 *> The factors L and U from the factorization A = P*L*U
71 *> as computed by SGETRF.
77 *> The leading dimension of the array A. LDA >= max(1,N).
83 *> If NORM = '1' or 'O', the 1-norm of the original matrix A.
84 *> If NORM = 'I', the infinity-norm of the original matrix A.
90 *> The reciprocal of the condition number of the matrix A,
91 *> computed as RCOND = 1/(norm(A) * norm(inv(A))).
96 *> WORK is REAL array, dimension (4*N)
101 *> IWORK is INTEGER array, dimension (N)
107 *> = 0: successful exit
108 *> < 0: if INFO = -i, the i-th argument had an illegal value
114 *> \author Univ. of Tennessee
115 *> \author Univ. of California Berkeley
116 *> \author Univ. of Colorado Denver
119 *> \date November 2011
121 *> \ingroup realGEcomputational
123 * =====================================================================
124 SUBROUTINE SGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
127 * -- LAPACK computational routine (version 3.4.0) --
128 * -- LAPACK is a software package provided by Univ. of Tennessee, --
129 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
132 * .. Scalar Arguments ..
137 * .. Array Arguments ..
139 REAL A( LDA, * ), WORK( * )
142 * =====================================================================
146 PARAMETER ( ONE = 1.0E+0, ZERO = 0.0E+0 )
148 * .. Local Scalars ..
151 INTEGER IX, KASE, KASE1
152 REAL AINVNM, SCALE, SL, SMLNUM, SU
157 * .. External Functions ..
161 EXTERNAL LSAME, ISAMAX, SLAMCH
163 * .. External Subroutines ..
164 EXTERNAL SLACN2, SLATRS, SRSCL, XERBLA
166 * .. Intrinsic Functions ..
169 * .. Executable Statements ..
171 * Test the input parameters.
174 ONENRM = NORM.EQ.'1' .OR. LSAME( NORM, 'O' )
175 IF( .NOT.ONENRM .AND. .NOT.LSAME( NORM, 'I' ) ) THEN
177 ELSE IF( N.LT.0 ) THEN
179 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
181 ELSE IF( ANORM.LT.ZERO ) THEN
185 CALL XERBLA( 'SGECON', -INFO )
189 * Quick return if possible
195 ELSE IF( ANORM.EQ.ZERO ) THEN
199 SMLNUM = SLAMCH( 'Safe minimum' )
201 * Estimate the norm of inv(A).
212 CALL SLACN2( N, WORK( N+1 ), WORK, IWORK, AINVNM, KASE, ISAVE )
214 IF( KASE.EQ.KASE1 ) THEN
216 * Multiply by inv(L).
218 CALL SLATRS( 'Lower', 'No transpose', 'Unit', NORMIN, N, A,
219 $ LDA, WORK, SL, WORK( 2*N+1 ), INFO )
221 * Multiply by inv(U).
223 CALL SLATRS( 'Upper', 'No transpose', 'Non-unit', NORMIN, N,
224 $ A, LDA, WORK, SU, WORK( 3*N+1 ), INFO )
227 * Multiply by inv(U**T).
229 CALL SLATRS( 'Upper', 'Transpose', 'Non-unit', NORMIN, N, A,
230 $ LDA, WORK, SU, WORK( 3*N+1 ), INFO )
232 * Multiply by inv(L**T).
234 CALL SLATRS( 'Lower', 'Transpose', 'Unit', NORMIN, N, A,
235 $ LDA, WORK, SL, WORK( 2*N+1 ), INFO )
238 * Divide X by 1/(SL*SU) if doing so will not cause overflow.
242 IF( SCALE.NE.ONE ) THEN
243 IX = ISAMAX( N, WORK, 1 )
244 IF( SCALE.LT.ABS( WORK( IX ) )*SMLNUM .OR. SCALE.EQ.ZERO )
246 CALL SRSCL( N, SCALE, WORK, 1 )
251 * Compute the estimate of the reciprocal condition number.
254 $ RCOND = ( ONE / AINVNM ) / ANORM