226 SUBROUTINE chesv_rk( UPLO, N, NRHS, A, LDA, E, IPIV, B, LDB, WORK,
235 INTEGER INFO, LDA, LDB, LWORK, N, NRHS
239 COMPLEX A( LDA, * ), B( LDB, * ), E( * ), WORK( * )
251 EXTERNAL lsame, sroundup_lwork
264 lquery = ( lwork.EQ.-1 )
265 IF( .NOT.lsame( uplo,
'U' ) .AND. .NOT.lsame( uplo,
'L' ) )
THEN
267 ELSE IF( n.LT.0 )
THEN
269 ELSE IF( nrhs.LT.0 )
THEN
271 ELSE IF( lda.LT.max( 1, n ) )
THEN
273 ELSE IF( ldb.LT.max( 1, n ) )
THEN
275 ELSE IF( lwork.LT.1 .AND. .NOT.lquery )
THEN
283 CALL chetrf_rk( uplo, n, a, lda, e, ipiv, work, -1, info )
284 lwkopt = int( work( 1 ) )
286 work( 1 ) = sroundup_lwork(lwkopt)
290 CALL xerbla(
'CHESV_RK ', -info )
292 ELSE IF( lquery )
THEN
298 CALL chetrf_rk( uplo, n, a, lda, e, ipiv, work, lwork, info )
304 CALL chetrs_3( uplo, n, nrhs, a, lda, e, ipiv, b, ldb, info )
308 work( 1 ) = sroundup_lwork(lwkopt)
subroutine xerbla(srname, info)
subroutine chesv_rk(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work, lwork, info)
CHESV_RK computes the solution to system of linear equations A * X = B for SY matrices
subroutine chetrf_rk(uplo, n, a, lda, e, ipiv, work, lwork, info)
CHETRF_RK computes the factorization of a complex Hermitian indefinite matrix using the bounded Bunch...
subroutine chetrs_3(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, info)
CHETRS_3