LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine dsycon_rook ( character  UPLO,
integer  N,
double precision, dimension( lda, * )  A,
integer  LDA,
integer, dimension( * )  IPIV,
double precision  ANORM,
double precision  RCOND,
double precision, dimension( * )  WORK,
integer, dimension( * )  IWORK,
integer  INFO 
)

DSYCON_ROOK

Download DSYCON_ROOK + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 DSYCON_ROOK estimates the reciprocal of the condition number (in the
 1-norm) of a real symmetric matrix A using the factorization
 A = U*D*U**T or A = L*D*L**T computed by DSYTRF_ROOK.

 An estimate is obtained for norm(inv(A)), and the reciprocal of the
 condition number is computed as RCOND = 1 / (ANORM * norm(inv(A))).
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          Specifies whether the details of the factorization are stored
          as an upper or lower triangular matrix.
          = 'U':  Upper triangular, form is A = U*D*U**T;
          = 'L':  Lower triangular, form is A = L*D*L**T.
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.
[in]A
          A is DOUBLE PRECISION array, dimension (LDA,N)
          The block diagonal matrix D and the multipliers used to
          obtain the factor U or L as computed by DSYTRF_ROOK.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,N).
[in]IPIV
          IPIV is INTEGER array, dimension (N)
          Details of the interchanges and the block structure of D
          as determined by DSYTRF_ROOK.
[in]ANORM
          ANORM is DOUBLE PRECISION
          The 1-norm of the original matrix A.
[out]RCOND
          RCOND is DOUBLE PRECISION
          The reciprocal of the condition number of the matrix A,
          computed as RCOND = 1/(ANORM * AINVNM), where AINVNM is an
          estimate of the 1-norm of inv(A) computed in this routine.
[out]WORK
          WORK is DOUBLE PRECISION array, dimension (2*N)
[out]IWORK
          IWORK is INTEGER array, dimension (N)
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0:  if INFO = -i, the i-th argument had an illegal value
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
April 2012
Contributors:

April 2012, Igor Kozachenko, Computer Science Division, University of California, Berkeley

September 2007, Sven Hammarling, Nicholas J. Higham, Craig Lucas, School of Mathematics, University of Manchester

Definition at line 146 of file dsycon_rook.f.

146 *
147 * -- LAPACK computational routine (version 3.4.1) --
148 * -- LAPACK is a software package provided by Univ. of Tennessee, --
149 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
150 * April 2012
151 *
152 * .. Scalar Arguments ..
153  CHARACTER uplo
154  INTEGER info, lda, n
155  DOUBLE PRECISION anorm, rcond
156 * ..
157 * .. Array Arguments ..
158  INTEGER ipiv( * ), iwork( * )
159  DOUBLE PRECISION a( lda, * ), work( * )
160 * ..
161 *
162 * =====================================================================
163 *
164 * .. Parameters ..
165  DOUBLE PRECISION one, zero
166  parameter ( one = 1.0d+0, zero = 0.0d+0 )
167 * ..
168 * .. Local Scalars ..
169  LOGICAL upper
170  INTEGER i, kase
171  DOUBLE PRECISION ainvnm
172 * ..
173 * .. Local Arrays ..
174  INTEGER isave( 3 )
175 * ..
176 * .. External Functions ..
177  LOGICAL lsame
178  EXTERNAL lsame
179 * ..
180 * .. External Subroutines ..
181  EXTERNAL dlacn2, dsytrs_rook, xerbla
182 * ..
183 * .. Intrinsic Functions ..
184  INTRINSIC max
185 * ..
186 * .. Executable Statements ..
187 *
188 * Test the input parameters.
189 *
190  info = 0
191  upper = lsame( uplo, 'U' )
192  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
193  info = -1
194  ELSE IF( n.LT.0 ) THEN
195  info = -2
196  ELSE IF( lda.LT.max( 1, n ) ) THEN
197  info = -4
198  ELSE IF( anorm.LT.zero ) THEN
199  info = -6
200  END IF
201  IF( info.NE.0 ) THEN
202  CALL xerbla( 'DSYCON_ROOK', -info )
203  RETURN
204  END IF
205 *
206 * Quick return if possible
207 *
208  rcond = zero
209  IF( n.EQ.0 ) THEN
210  rcond = one
211  RETURN
212  ELSE IF( anorm.LE.zero ) THEN
213  RETURN
214  END IF
215 *
216 * Check that the diagonal matrix D is nonsingular.
217 *
218  IF( upper ) THEN
219 *
220 * Upper triangular storage: examine D from bottom to top
221 *
222  DO 10 i = n, 1, -1
223  IF( ipiv( i ).GT.0 .AND. a( i, i ).EQ.zero )
224  $ RETURN
225  10 CONTINUE
226  ELSE
227 *
228 * Lower triangular storage: examine D from top to bottom.
229 *
230  DO 20 i = 1, n
231  IF( ipiv( i ).GT.0 .AND. a( i, i ).EQ.zero )
232  $ RETURN
233  20 CONTINUE
234  END IF
235 *
236 * Estimate the 1-norm of the inverse.
237 *
238  kase = 0
239  30 CONTINUE
240  CALL dlacn2( n, work( n+1 ), work, iwork, ainvnm, kase, isave )
241  IF( kase.NE.0 ) THEN
242 *
243 * Multiply by inv(L*D*L**T) or inv(U*D*U**T).
244 *
245  CALL dsytrs_rook( uplo, n, 1, a, lda, ipiv, work, n, info )
246  GO TO 30
247  END IF
248 *
249 * Compute the estimate of the reciprocal condition number.
250 *
251  IF( ainvnm.NE.zero )
252  $ rcond = ( one / ainvnm ) / anorm
253 *
254  RETURN
255 *
256 * End of DSYCON_ROOK
257 *
subroutine dsytrs_rook(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
DSYTRS_ROOK
Definition: dsytrs_rook.f:138
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55
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

Here is the call graph for this function:

Here is the caller graph for this function: