203 SUBROUTINE chesv_rook( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK,
212 INTEGER INFO, LDA, LDB, LWORK, N, NRHS
216 COMPLEX A( LDA, * ), B( LDB, * ), WORK( * )
229 EXTERNAL lsame, ilaenv, sroundup_lwork
242 lquery = ( lwork.EQ.-1 )
243 IF( .NOT.lsame( uplo,
'U' ) .AND. .NOT.lsame( uplo,
'L' ) )
THEN
245 ELSE IF( n.LT.0 )
THEN
247 ELSE IF( nrhs.LT.0 )
THEN
249 ELSE IF( lda.LT.max( 1, n ) )
THEN
251 ELSE IF( ldb.LT.max( 1, n ) )
THEN
253 ELSE IF( lwork.LT.1 .AND. .NOT.lquery )
THEN
261 nb = ilaenv( 1,
'CHETRF_ROOK', uplo, n, -1, -1, -1 )
264 work( 1 ) = sroundup_lwork(lwkopt)
268 CALL xerbla(
'CHESV_ROOK ', -info )
270 ELSE IF( lquery )
THEN
276 CALL chetrf_rook( uplo, n, a, lda, ipiv, work, lwork, info )
283 CALL chetrs_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb, info )
287 work( 1 ) = sroundup_lwork(lwkopt)
subroutine xerbla(srname, info)
subroutine chesv_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)
CHESV_ROOK computes the solution to a system of linear equations A * X = B for HE matrices using the ...
subroutine chetrf_rook(uplo, n, a, lda, ipiv, work, lwork, info)
CHETRF_ROOK computes the factorization of a complex Hermitian indefinite matrix using the bounded Bun...
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...