LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ checon_rook()

subroutine checon_rook ( character  uplo,
integer  n,
complex, dimension( lda, * )  a,
integer  lda,
integer, dimension( * )  ipiv,
real  anorm,
real  rcond,
complex, dimension( * )  work,
integer  info 
)

CHECON_ROOK estimates the reciprocal of the condition number fort HE matrices using factorization obtained with one of the bounded diagonal pivoting methods (max 2 interchanges)

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

Purpose:
 CHECON_ROOK estimates the reciprocal of the condition number of a complex
 Hermitian matrix A using the factorization A = U*D*U**H or
 A = L*D*L**H computed by CHETRF_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**H;
          = 'L':  Lower triangular, form is A = L*D*L**H.
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.
[in]A
          A is COMPLEX array, dimension (LDA,N)
          The block diagonal matrix D and the multipliers used to
          obtain the factor U or L as computed by CHETRF_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 CHETRF_ROOK.
[in]ANORM
          ANORM is REAL
          The 1-norm of the original matrix A.
[out]RCOND
          RCOND is REAL
          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 COMPLEX array, dimension (2*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.
Contributors:
  December 2016,  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 137 of file checon_rook.f.

139*
140* -- LAPACK computational routine --
141* -- LAPACK is a software package provided by Univ. of Tennessee, --
142* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
143*
144* .. Scalar Arguments ..
145 CHARACTER UPLO
146 INTEGER INFO, LDA, N
147 REAL ANORM, RCOND
148* ..
149* .. Array Arguments ..
150 INTEGER IPIV( * )
151 COMPLEX A( LDA, * ), WORK( * )
152* ..
153*
154* =====================================================================
155*
156* .. Parameters ..
157 REAL ONE, ZERO
158 parameter( one = 1.0e+0, zero = 0.0e+0 )
159* ..
160* .. Local Scalars ..
161 LOGICAL UPPER
162 INTEGER I, KASE
163 REAL AINVNM
164* ..
165* .. Local Arrays ..
166 INTEGER ISAVE( 3 )
167* ..
168* .. External Functions ..
169 LOGICAL LSAME
170 EXTERNAL lsame
171* ..
172* .. External Subroutines ..
173 EXTERNAL chetrs_rook, clacn2, xerbla
174* ..
175* .. Intrinsic Functions ..
176 INTRINSIC max
177* ..
178* .. Executable Statements ..
179*
180* Test the input parameters.
181*
182 info = 0
183 upper = lsame( uplo, 'U' )
184 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
185 info = -1
186 ELSE IF( n.LT.0 ) THEN
187 info = -2
188 ELSE IF( lda.LT.max( 1, n ) ) THEN
189 info = -4
190 ELSE IF( anorm.LT.zero ) THEN
191 info = -6
192 END IF
193 IF( info.NE.0 ) THEN
194 CALL xerbla( 'CHECON_ROOK', -info )
195 RETURN
196 END IF
197*
198* Quick return if possible
199*
200 rcond = zero
201 IF( n.EQ.0 ) THEN
202 rcond = one
203 RETURN
204 ELSE IF( anorm.LE.zero ) THEN
205 RETURN
206 END IF
207*
208* Check that the diagonal matrix D is nonsingular.
209*
210 IF( upper ) THEN
211*
212* Upper triangular storage: examine D from bottom to top
213*
214 DO 10 i = n, 1, -1
215 IF( ipiv( i ).GT.0 .AND. a( i, i ).EQ.zero )
216 $ RETURN
217 10 CONTINUE
218 ELSE
219*
220* Lower triangular storage: examine D from top to bottom.
221*
222 DO 20 i = 1, n
223 IF( ipiv( i ).GT.0 .AND. a( i, i ).EQ.zero )
224 $ RETURN
225 20 CONTINUE
226 END IF
227*
228* Estimate the 1-norm of the inverse.
229*
230 kase = 0
231 30 CONTINUE
232 CALL clacn2( n, work( n+1 ), work, ainvnm, kase, isave )
233 IF( kase.NE.0 ) THEN
234*
235* Multiply by inv(L*D*L**H) or inv(U*D*U**H).
236*
237 CALL chetrs_rook( uplo, n, 1, a, lda, ipiv, work, n, info )
238 GO TO 30
239 END IF
240*
241* Compute the estimate of the reciprocal condition number.
242*
243 IF( ainvnm.NE.zero )
244 $ rcond = ( one / ainvnm ) / anorm
245*
246 RETURN
247*
248* End of CHECON_ROOK
249*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine chetrs_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)
CHETRS_ROOK computes the solution to a system of linear equations A * X = B for HE matrices using fac...
subroutine clacn2(n, v, x, est, kase, isave)
CLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
Definition clacn2.f:133
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: