205 SUBROUTINE chesv_rook( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK,
215 INTEGER INFO, LDA, LDB, LWORK, N, NRHS
219 COMPLEX A( lda, * ), B( ldb, * ), WORK( * )
231 EXTERNAL lsame, ilaenv
244 lquery = ( lwork.EQ.-1 )
245 IF( .NOT.lsame( uplo,
'U' ) .AND. .NOT.lsame( uplo,
'L' ) )
THEN
247 ELSE IF( n.LT.0 )
THEN
249 ELSE IF( nrhs.LT.0 )
THEN
251 ELSE IF( lda.LT.max( 1, n ) )
THEN
253 ELSE IF( ldb.LT.max( 1, n ) )
THEN
255 ELSE IF( lwork.LT.1 .AND. .NOT.lquery )
THEN
263 nb = ilaenv( 1,
'CHETRF_ROOK', uplo, n, -1, -1, -1 )
270 CALL xerbla(
'CHESV_ROOK ', -info )
272 ELSE IF( lquery )
THEN
278 CALL chetrf_rook( uplo, n, a, lda, ipiv, work, lwork, info )
285 CALL chetrs_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb, info )
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 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 xerbla(SRNAME, INFO)
XERBLA
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 ...