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

◆ zla_porcond_c()

double precision function zla_porcond_c ( character  uplo,
integer  n,
complex*16, dimension( lda, * )  a,
integer  lda,
complex*16, dimension( ldaf, * )  af,
integer  ldaf,
double precision, dimension( * )  c,
logical  capply,
integer  info,
complex*16, dimension( * )  work,
double precision, dimension( * )  rwork 
)

ZLA_PORCOND_C computes the infinity norm condition number of op(A)*inv(diag(c)) for Hermitian positive-definite matrices.

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

Purpose:
    ZLA_PORCOND_C Computes the infinity norm condition number of
    op(A) * inv(diag(C)) where C is a DOUBLE PRECISION vector
Parameters
[in]UPLO
          UPLO is CHARACTER*1
       = 'U':  Upper triangle of A is stored;
       = 'L':  Lower triangle of A is stored.
[in]N
          N is INTEGER
     The number of linear equations, i.e., the order of the
     matrix A.  N >= 0.
[in]A
          A is COMPLEX*16 array, dimension (LDA,N)
     On entry, the N-by-N matrix A
[in]LDA
          LDA is INTEGER
     The leading dimension of the array A.  LDA >= max(1,N).
[in]AF
          AF is COMPLEX*16 array, dimension (LDAF,N)
     The triangular factor U or L from the Cholesky factorization
     A = U**H*U or A = L*L**H, as computed by ZPOTRF.
[in]LDAF
          LDAF is INTEGER
     The leading dimension of the array AF.  LDAF >= max(1,N).
[in]C
          C is DOUBLE PRECISION array, dimension (N)
     The vector C in the formula op(A) * inv(diag(C)).
[in]CAPPLY
          CAPPLY is LOGICAL
     If .TRUE. then access the vector C in the formula above.
[out]INFO
          INFO is INTEGER
       = 0:  Successful exit.
     i > 0:  The ith argument is invalid.
[out]WORK
          WORK is COMPLEX*16 array, dimension (2*N).
     Workspace.
[out]RWORK
          RWORK is DOUBLE PRECISION array, dimension (N).
     Workspace.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 129 of file zla_porcond_c.f.

132*
133* -- LAPACK computational routine --
134* -- LAPACK is a software package provided by Univ. of Tennessee, --
135* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
136*
137* .. Scalar Arguments ..
138 CHARACTER UPLO
139 LOGICAL CAPPLY
140 INTEGER N, LDA, LDAF, INFO
141* ..
142* .. Array Arguments ..
143 COMPLEX*16 A( LDA, * ), AF( LDAF, * ), WORK( * )
144 DOUBLE PRECISION C( * ), RWORK( * )
145* ..
146*
147* =====================================================================
148*
149* .. Local Scalars ..
150 INTEGER KASE
151 DOUBLE PRECISION AINVNM, ANORM, TMP
152 INTEGER I, J
153 LOGICAL UP, UPPER
154 COMPLEX*16 ZDUM
155* ..
156* .. Local Arrays ..
157 INTEGER ISAVE( 3 )
158* ..
159* .. External Functions ..
160 LOGICAL LSAME
161 EXTERNAL lsame
162* ..
163* .. External Subroutines ..
164 EXTERNAL zlacn2, zpotrs, xerbla
165* ..
166* .. Intrinsic Functions ..
167 INTRINSIC abs, max, real, dimag
168* ..
169* .. Statement Functions ..
170 DOUBLE PRECISION CABS1
171* ..
172* .. Statement Function Definitions ..
173 cabs1( zdum ) = abs( dble( zdum ) ) + abs( dimag( zdum ) )
174* ..
175* .. Executable Statements ..
176*
177 zla_porcond_c = 0.0d+0
178*
179 info = 0
180 upper = lsame( uplo, 'U' )
181 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
182 info = -1
183 ELSE IF( n.LT.0 ) THEN
184 info = -2
185 ELSE IF( lda.LT.max( 1, n ) ) THEN
186 info = -4
187 ELSE IF( ldaf.LT.max( 1, n ) ) THEN
188 info = -6
189 END IF
190 IF( info.NE.0 ) THEN
191 CALL xerbla( 'ZLA_PORCOND_C', -info )
192 RETURN
193 END IF
194 up = .false.
195 IF ( lsame( uplo, 'U' ) ) up = .true.
196*
197* Compute norm of op(A)*op2(C).
198*
199 anorm = 0.0d+0
200 IF ( up ) THEN
201 DO i = 1, n
202 tmp = 0.0d+0
203 IF ( capply ) THEN
204 DO j = 1, i
205 tmp = tmp + cabs1( a( j, i ) ) / c( j )
206 END DO
207 DO j = i+1, n
208 tmp = tmp + cabs1( a( i, j ) ) / c( j )
209 END DO
210 ELSE
211 DO j = 1, i
212 tmp = tmp + cabs1( a( j, i ) )
213 END DO
214 DO j = i+1, n
215 tmp = tmp + cabs1( a( i, j ) )
216 END DO
217 END IF
218 rwork( i ) = tmp
219 anorm = max( anorm, tmp )
220 END DO
221 ELSE
222 DO i = 1, n
223 tmp = 0.0d+0
224 IF ( capply ) THEN
225 DO j = 1, i
226 tmp = tmp + cabs1( a( i, j ) ) / c( j )
227 END DO
228 DO j = i+1, n
229 tmp = tmp + cabs1( a( j, i ) ) / c( j )
230 END DO
231 ELSE
232 DO j = 1, i
233 tmp = tmp + cabs1( a( i, j ) )
234 END DO
235 DO j = i+1, n
236 tmp = tmp + cabs1( a( j, i ) )
237 END DO
238 END IF
239 rwork( i ) = tmp
240 anorm = max( anorm, tmp )
241 END DO
242 END IF
243*
244* Quick return if possible.
245*
246 IF( n.EQ.0 ) THEN
247 zla_porcond_c = 1.0d+0
248 RETURN
249 ELSE IF( anorm .EQ. 0.0d+0 ) THEN
250 RETURN
251 END IF
252*
253* Estimate the norm of inv(op(A)).
254*
255 ainvnm = 0.0d+0
256*
257 kase = 0
258 10 CONTINUE
259 CALL zlacn2( n, work( n+1 ), work, ainvnm, kase, isave )
260 IF( kase.NE.0 ) THEN
261 IF( kase.EQ.2 ) THEN
262*
263* Multiply by R.
264*
265 DO i = 1, n
266 work( i ) = work( i ) * rwork( i )
267 END DO
268*
269 IF ( up ) THEN
270 CALL zpotrs( 'U', n, 1, af, ldaf,
271 $ work, n, info )
272 ELSE
273 CALL zpotrs( 'L', n, 1, af, ldaf,
274 $ work, n, info )
275 ENDIF
276*
277* Multiply by inv(C).
278*
279 IF ( capply ) THEN
280 DO i = 1, n
281 work( i ) = work( i ) * c( i )
282 END DO
283 END IF
284 ELSE
285*
286* Multiply by inv(C**H).
287*
288 IF ( capply ) THEN
289 DO i = 1, n
290 work( i ) = work( i ) * c( i )
291 END DO
292 END IF
293*
294 IF ( up ) THEN
295 CALL zpotrs( 'U', n, 1, af, ldaf,
296 $ work, n, info )
297 ELSE
298 CALL zpotrs( 'L', n, 1, af, ldaf,
299 $ work, n, info )
300 END IF
301*
302* Multiply by R.
303*
304 DO i = 1, n
305 work( i ) = work( i ) * rwork( i )
306 END DO
307 END IF
308 GO TO 10
309 END IF
310*
311* Compute the estimate of the reciprocal condition number.
312*
313 IF( ainvnm .NE. 0.0d+0 )
314 $ zla_porcond_c = 1.0d+0 / ainvnm
315*
316 RETURN
317*
318* End of ZLA_PORCOND_C
319*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
double precision function zla_porcond_c(uplo, n, a, lda, af, ldaf, c, capply, info, work, rwork)
ZLA_PORCOND_C computes the infinity norm condition number of op(A)*inv(diag(c)) for Hermitian positiv...
subroutine zlacn2(n, v, x, est, kase, isave)
ZLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
Definition zlacn2.f:133
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine zpotrs(uplo, n, nrhs, a, lda, b, ldb, info)
ZPOTRS
Definition zpotrs.f:110
Here is the call graph for this function:
Here is the caller graph for this function: