280 SUBROUTINE chesvx( FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV,
282 $ LDB, X, LDX, RCOND, FERR, BERR, WORK, LWORK,
291 INTEGER INFO, LDA, LDAF, LDB, LDX, LWORK, N, NRHS
296 REAL BERR( * ), FERR( * ), RWORK( * )
297 COMPLEX A( LDA, * ), AF( LDAF, * ), B( LDB, * ),
298 $ work( * ), x( ldx, * )
305 PARAMETER ( ZERO = 0.0e+0 )
308 LOGICAL LQUERY, NOFACT
309 INTEGER LWKMIN, LWKOPT, NB
315 REAL CLANHE, SLAMCH, SROUNDUP_LWORK
316 EXTERNAL ilaenv, lsame, clanhe, slamch,
331 nofact = lsame( fact,
'N' )
332 lquery = ( lwork.EQ.-1 )
333 lwkmin = max( 1, 2*n )
334 IF( .NOT.nofact .AND. .NOT.lsame( fact,
'F' ) )
THEN
336 ELSE IF( .NOT.lsame( uplo,
'U' ) .AND.
337 $ .NOT.lsame( uplo,
'L' ) )
340 ELSE IF( n.LT.0 )
THEN
342 ELSE IF( nrhs.LT.0 )
THEN
344 ELSE IF( lda.LT.max( 1, n ) )
THEN
346 ELSE IF( ldaf.LT.max( 1, n ) )
THEN
348 ELSE IF( ldb.LT.max( 1, n ) )
THEN
350 ELSE IF( ldx.LT.max( 1, n ) )
THEN
352 ELSE IF( lwork.LT.lwkmin .AND. .NOT.lquery )
THEN
359 nb = ilaenv( 1,
'CHETRF', uplo, n, -1, -1, -1 )
360 lwkopt = max( lwkopt, n*nb )
362 work( 1 ) = sroundup_lwork( lwkopt )
366 CALL xerbla(
'CHESVX', -info )
368 ELSE IF( lquery )
THEN
376 CALL clacpy( uplo, n, n, a, lda, af, ldaf )
377 CALL chetrf( uplo, n, af, ldaf, ipiv, work, lwork, info )
389 anorm = clanhe(
'I', uplo, n, a, lda, rwork )
393 CALL checon( uplo, n, af, ldaf, ipiv, anorm, rcond, work,
398 CALL clacpy(
'Full', n, nrhs, b, ldb, x, ldx )
399 CALL chetrs( uplo, n, nrhs, af, ldaf, ipiv, x, ldx, info )
404 CALL cherfs( uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x,
405 $ ldx, ferr, berr, work, rwork, info )
409 IF( rcond.LT.slamch(
'Epsilon' ) )
412 work( 1 ) = sroundup_lwork( lwkopt )
subroutine cherfs(uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, ferr, berr, work, rwork, info)
CHERFS
subroutine chesvx(fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, lwork, rwork, info)
CHESVX computes the solution to system of linear equations A * X = B for HE matrices