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

◆ cpbcon()

subroutine cpbcon ( character  uplo,
integer  n,
integer  kd,
complex, dimension( ldab, * )  ab,
integer  ldab,
real  anorm,
real  rcond,
complex, dimension( * )  work,
real, dimension( * )  rwork,
integer  info 
)

CPBCON

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

Purpose:
 CPBCON estimates the reciprocal of the condition number (in the
 1-norm) of a complex Hermitian positive definite band matrix using
 the Cholesky factorization A = U**H*U or A = L*L**H computed by
 CPBTRF.

 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
          = 'U':  Upper triangular factor stored in AB;
          = 'L':  Lower triangular factor stored in AB.
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.
[in]KD
          KD is INTEGER
          The number of superdiagonals of the matrix A if UPLO = 'U',
          or the number of sub-diagonals if UPLO = 'L'.  KD >= 0.
[in]AB
          AB is COMPLEX array, dimension (LDAB,N)
          The triangular factor U or L from the Cholesky factorization
          A = U**H*U or A = L*L**H of the band matrix A, stored in the
          first KD+1 rows of the array.  The j-th column of U or L is
          stored in the j-th column of the array AB as follows:
          if UPLO ='U', AB(kd+1+i-j,j) = U(i,j) for max(1,j-kd)<=i<=j;
          if UPLO ='L', AB(1+i-j,j)    = L(i,j) for j<=i<=min(n,j+kd).
[in]LDAB
          LDAB is INTEGER
          The leading dimension of the array AB.  LDAB >= KD+1.
[in]ANORM
          ANORM is REAL
          The 1-norm (or infinity-norm) of the Hermitian band 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]RWORK
          RWORK is REAL 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.

Definition at line 131 of file cpbcon.f.

133*
134* -- LAPACK computational routine --
135* -- LAPACK is a software package provided by Univ. of Tennessee, --
136* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
137*
138* .. Scalar Arguments ..
139 CHARACTER UPLO
140 INTEGER INFO, KD, LDAB, N
141 REAL ANORM, RCOND
142* ..
143* .. Array Arguments ..
144 REAL RWORK( * )
145 COMPLEX AB( LDAB, * ), WORK( * )
146* ..
147*
148* =====================================================================
149*
150* .. Parameters ..
151 REAL ONE, ZERO
152 parameter( one = 1.0e+0, zero = 0.0e+0 )
153* ..
154* .. Local Scalars ..
155 LOGICAL UPPER
156 CHARACTER NORMIN
157 INTEGER IX, KASE
158 REAL AINVNM, SCALE, SCALEL, SCALEU, SMLNUM
159 COMPLEX ZDUM
160* ..
161* .. Local Arrays ..
162 INTEGER ISAVE( 3 )
163* ..
164* .. External Functions ..
165 LOGICAL LSAME
166 INTEGER ICAMAX
167 REAL SLAMCH
168 EXTERNAL lsame, icamax, slamch
169* ..
170* .. External Subroutines ..
171 EXTERNAL clacn2, clatbs, csrscl, xerbla
172* ..
173* .. Intrinsic Functions ..
174 INTRINSIC abs, aimag, real
175* ..
176* .. Statement Functions ..
177 REAL CABS1
178* ..
179* .. Statement Function definitions ..
180 cabs1( zdum ) = abs( real( zdum ) ) + abs( aimag( zdum ) )
181* ..
182* .. Executable Statements ..
183*
184* Test the input parameters.
185*
186 info = 0
187 upper = lsame( uplo, 'U' )
188 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
189 info = -1
190 ELSE IF( n.LT.0 ) THEN
191 info = -2
192 ELSE IF( kd.LT.0 ) THEN
193 info = -3
194 ELSE IF( ldab.LT.kd+1 ) THEN
195 info = -5
196 ELSE IF( anorm.LT.zero ) THEN
197 info = -6
198 END IF
199 IF( info.NE.0 ) THEN
200 CALL xerbla( 'CPBCON', -info )
201 RETURN
202 END IF
203*
204* Quick return if possible
205*
206 rcond = zero
207 IF( n.EQ.0 ) THEN
208 rcond = one
209 RETURN
210 ELSE IF( anorm.EQ.zero ) THEN
211 RETURN
212 END IF
213*
214 smlnum = slamch( 'Safe minimum' )
215*
216* Estimate the 1-norm of the inverse.
217*
218 kase = 0
219 normin = 'N'
220 10 CONTINUE
221 CALL clacn2( n, work( n+1 ), work, ainvnm, kase, isave )
222 IF( kase.NE.0 ) THEN
223 IF( upper ) THEN
224*
225* Multiply by inv(U**H).
226*
227 CALL clatbs( 'Upper', 'Conjugate transpose', 'Non-unit',
228 $ normin, n, kd, ab, ldab, work, scalel, rwork,
229 $ info )
230 normin = 'Y'
231*
232* Multiply by inv(U).
233*
234 CALL clatbs( 'Upper', 'No transpose', 'Non-unit', normin, n,
235 $ kd, ab, ldab, work, scaleu, rwork, info )
236 ELSE
237*
238* Multiply by inv(L).
239*
240 CALL clatbs( 'Lower', 'No transpose', 'Non-unit', normin, n,
241 $ kd, ab, ldab, work, scalel, rwork, info )
242 normin = 'Y'
243*
244* Multiply by inv(L**H).
245*
246 CALL clatbs( 'Lower', 'Conjugate transpose', 'Non-unit',
247 $ normin, n, kd, ab, ldab, work, scaleu, rwork,
248 $ info )
249 END IF
250*
251* Multiply by 1/SCALE if doing so will not cause overflow.
252*
253 scale = scalel*scaleu
254 IF( scale.NE.one ) THEN
255 ix = icamax( n, work, 1 )
256 IF( scale.LT.cabs1( work( ix ) )*smlnum .OR. scale.EQ.zero )
257 $ GO TO 20
258 CALL csrscl( n, scale, work, 1 )
259 END IF
260 GO TO 10
261 END IF
262*
263* Compute the estimate of the reciprocal condition number.
264*
265 IF( ainvnm.NE.zero )
266 $ rcond = ( one / ainvnm ) / anorm
267*
268 20 CONTINUE
269*
270 RETURN
271*
272* End of CPBCON
273*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function icamax(n, cx, incx)
ICAMAX
Definition icamax.f:71
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
real function slamch(cmach)
SLAMCH
Definition slamch.f:68
subroutine clatbs(uplo, trans, diag, normin, n, kd, ab, ldab, x, scale, cnorm, info)
CLATBS solves a triangular banded system of equations.
Definition clatbs.f:243
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine csrscl(n, sa, sx, incx)
CSRSCL multiplies a vector by the reciprocal of a real scalar.
Definition csrscl.f:84
Here is the call graph for this function:
Here is the caller graph for this function: