LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
dgecon.f
Go to the documentation of this file.
1 *> \brief \b DGECON
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download DGECON + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dgecon.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dgecon.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgecon.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE DGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
22 * INFO )
23 *
24 * .. Scalar Arguments ..
25 * CHARACTER NORM
26 * INTEGER INFO, LDA, N
27 * DOUBLE PRECISION ANORM, RCOND
28 * ..
29 * .. Array Arguments ..
30 * INTEGER IWORK( * )
31 * DOUBLE PRECISION A( LDA, * ), WORK( * )
32 * ..
33 *
34 *
35 *> \par Purpose:
36 * =============
37 *>
38 *> \verbatim
39 *>
40 *> DGECON 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 DGETRF.
43 *>
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)) ).
47 *> \endverbatim
48 *
49 * Arguments:
50 * ==========
51 *
52 *> \param[in] NORM
53 *> \verbatim
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.
59 *> \endverbatim
60 *>
61 *> \param[in] N
62 *> \verbatim
63 *> N is INTEGER
64 *> The order of the matrix A. N >= 0.
65 *> \endverbatim
66 *>
67 *> \param[in] A
68 *> \verbatim
69 *> A is DOUBLE PRECISION array, dimension (LDA,N)
70 *> The factors L and U from the factorization A = P*L*U
71 *> as computed by DGETRF.
72 *> \endverbatim
73 *>
74 *> \param[in] LDA
75 *> \verbatim
76 *> LDA is INTEGER
77 *> The leading dimension of the array A. LDA >= max(1,N).
78 *> \endverbatim
79 *>
80 *> \param[in] ANORM
81 *> \verbatim
82 *> ANORM is DOUBLE PRECISION
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.
85 *> \endverbatim
86 *>
87 *> \param[out] RCOND
88 *> \verbatim
89 *> RCOND is DOUBLE PRECISION
90 *> The reciprocal of the condition number of the matrix A,
91 *> computed as RCOND = 1/(norm(A) * norm(inv(A))).
92 *> \endverbatim
93 *>
94 *> \param[out] WORK
95 *> \verbatim
96 *> WORK is DOUBLE PRECISION array, dimension (4*N)
97 *> \endverbatim
98 *>
99 *> \param[out] IWORK
100 *> \verbatim
101 *> IWORK is INTEGER array, dimension (N)
102 *> \endverbatim
103 *>
104 *> \param[out] INFO
105 *> \verbatim
106 *> INFO is INTEGER
107 *> = 0: successful exit
108 *> < 0: if INFO = -i, the i-th argument had an illegal value
109 *> \endverbatim
110 *
111 * Authors:
112 * ========
113 *
114 *> \author Univ. of Tennessee
115 *> \author Univ. of California Berkeley
116 *> \author Univ. of Colorado Denver
117 *> \author NAG Ltd.
118 *
119 *> \date November 2011
120 *
121 *> \ingroup doubleGEcomputational
122 *
123 * =====================================================================
124  SUBROUTINE dgecon( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
125  $ info )
126 *
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..--
130 * November 2011
131 *
132 * .. Scalar Arguments ..
133  CHARACTER NORM
134  INTEGER INFO, LDA, N
135  DOUBLE PRECISION ANORM, RCOND
136 * ..
137 * .. Array Arguments ..
138  INTEGER IWORK( * )
139  DOUBLE PRECISION A( lda, * ), WORK( * )
140 * ..
141 *
142 * =====================================================================
143 *
144 * .. Parameters ..
145  DOUBLE PRECISION ONE, ZERO
146  parameter ( one = 1.0d+0, zero = 0.0d+0 )
147 * ..
148 * .. Local Scalars ..
149  LOGICAL ONENRM
150  CHARACTER NORMIN
151  INTEGER IX, KASE, KASE1
152  DOUBLE PRECISION AINVNM, SCALE, SL, SMLNUM, SU
153 * ..
154 * .. Local Arrays ..
155  INTEGER ISAVE( 3 )
156 * ..
157 * .. External Functions ..
158  LOGICAL LSAME
159  INTEGER IDAMAX
160  DOUBLE PRECISION DLAMCH
161  EXTERNAL lsame, idamax, dlamch
162 * ..
163 * .. External Subroutines ..
164  EXTERNAL dlacn2, dlatrs, drscl, xerbla
165 * ..
166 * .. Intrinsic Functions ..
167  INTRINSIC abs, max
168 * ..
169 * .. Executable Statements ..
170 *
171 * Test the input parameters.
172 *
173  info = 0
174  onenrm = norm.EQ.'1' .OR. lsame( norm, 'O' )
175  IF( .NOT.onenrm .AND. .NOT.lsame( norm, 'I' ) ) THEN
176  info = -1
177  ELSE IF( n.LT.0 ) THEN
178  info = -2
179  ELSE IF( lda.LT.max( 1, n ) ) THEN
180  info = -4
181  ELSE IF( anorm.LT.zero ) THEN
182  info = -5
183  END IF
184  IF( info.NE.0 ) THEN
185  CALL xerbla( 'DGECON', -info )
186  RETURN
187  END IF
188 *
189 * Quick return if possible
190 *
191  rcond = zero
192  IF( n.EQ.0 ) THEN
193  rcond = one
194  RETURN
195  ELSE IF( anorm.EQ.zero ) THEN
196  RETURN
197  END IF
198 *
199  smlnum = dlamch( 'Safe minimum' )
200 *
201 * Estimate the norm of inv(A).
202 *
203  ainvnm = zero
204  normin = 'N'
205  IF( onenrm ) THEN
206  kase1 = 1
207  ELSE
208  kase1 = 2
209  END IF
210  kase = 0
211  10 CONTINUE
212  CALL dlacn2( n, work( n+1 ), work, iwork, ainvnm, kase, isave )
213  IF( kase.NE.0 ) THEN
214  IF( kase.EQ.kase1 ) THEN
215 *
216 * Multiply by inv(L).
217 *
218  CALL dlatrs( 'Lower', 'No transpose', 'Unit', normin, n, a,
219  $ lda, work, sl, work( 2*n+1 ), info )
220 *
221 * Multiply by inv(U).
222 *
223  CALL dlatrs( 'Upper', 'No transpose', 'Non-unit', normin, n,
224  $ a, lda, work, su, work( 3*n+1 ), info )
225  ELSE
226 *
227 * Multiply by inv(U**T).
228 *
229  CALL dlatrs( 'Upper', 'Transpose', 'Non-unit', normin, n, a,
230  $ lda, work, su, work( 3*n+1 ), info )
231 *
232 * Multiply by inv(L**T).
233 *
234  CALL dlatrs( 'Lower', 'Transpose', 'Unit', normin, n, a,
235  $ lda, work, sl, work( 2*n+1 ), info )
236  END IF
237 *
238 * Divide X by 1/(SL*SU) if doing so will not cause overflow.
239 *
240  scale = sl*su
241  normin = 'Y'
242  IF( scale.NE.one ) THEN
243  ix = idamax( n, work, 1 )
244  IF( scale.LT.abs( work( ix ) )*smlnum .OR. scale.EQ.zero )
245  $ GO TO 20
246  CALL drscl( n, scale, work, 1 )
247  END IF
248  GO TO 10
249  END IF
250 *
251 * Compute the estimate of the reciprocal condition number.
252 *
253  IF( ainvnm.NE.zero )
254  $ rcond = ( one / ainvnm ) / anorm
255 *
256  20 CONTINUE
257  RETURN
258 *
259 * End of DGECON
260 *
261  END
subroutine dlatrs(UPLO, TRANS, DIAG, NORMIN, N, A, LDA, X, SCALE, CNORM, INFO)
DLATRS solves a triangular system of equations with the scale factor set to prevent overflow...
Definition: dlatrs.f:240
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine drscl(N, SA, SX, INCX)
DRSCL multiplies a vector by the reciprocal of a real scalar.
Definition: drscl.f:86
subroutine dgecon(NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK, INFO)
DGECON
Definition: dgecon.f:126
subroutine dlacn2(N, V, X, ISGN, EST, KASE, ISAVE)
DLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
Definition: dlacn2.f:138