next up previous contents index
Next: Computational Routines for the Up: Computational Routines Previous: Computational Routines for the   Contents   Index


Computational Routines for the Generalized Symmetric Definite Eigenproblem

LA_SYGST / LA_HEGST
Real and complex versions.


SUBROUTINE LA_SYGST / LA_HEGST( ITYPE, & 

UPLO, N, A, LDA, B, LDB, INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: ITYPE, LDA, LDB, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(IN) :: B(LDB,*)
type(wp), INTENT(INOUT) :: A(LDA,*)
where
type ::= REAL $\mid$ COMPLEX
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


LA_SYGST / LA_HEGST reduces a real symmetric / complex Hermitian definite generalized eigenproblem to standard form.

References: See  [1] and [9,20].
-----------------------------------

LA_SPGST / LA_HPGST
Real and complex versions.


SUBROUTINE LA_SPGST / LA_HPGST( ITYPE, & 

UPLO, N, AP, BP, INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: ITYPE, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(IN) :: BP(*)
type(wp), INTENT(INOUT) :: AP(*)
where
type ::= REAL $\mid$ COMPLEX
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


LA_SPGST / LA_HPGST reduces a real symmetric / complex Hermitian definite generalized eigenproblem to standard form, using packed storage.

References: See  [1] and [9,20].
-----------------------------------

LA_PBSTF
Real and complex versions.


SUBROUTINE LA_PBSTF( UPLO, N, KD, AB, & 

LDAB, INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO
INTEGER, INTENT(IN) :: KD, LDAB, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(INOUT) :: AB(LDAB,*)
where
type ::= REAL $\mid$ COMPLEX
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


LA_PBSTF computes a split Cholesky factorization of a real symmetric / complex Hermitian positive definite band matrix $A$.
References: See  [1] and [9,20].
-----------------------------------

LA_SBGST / LA_HBGST
Real version.


SUBROUTINE LA_SBGST( VECT, UPLO, N, & 

KA, KB, AB, LDAB, BB, LDBB, X, LDX, &
WORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO, &
VECT
INTEGER, INTENT(IN) :: KA, KB, LDAB, &
LDBB, LDX, N
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(IN) :: BB(LDBB,*)
REAL(wp), INTENT(INOUT) :: AB(LDAB,*)
REAL(wp), INTENT(OUT) :: WORK(*), X(LDX,*)
where
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


Complex version.


 SUBROUTINE LA_HBGST( VECT, UPLO, N, & 

KA, KB, AB, LDAB, BB, LDBB, X, LDX, &
WORK, RWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: UPLO, &
VECT
INTEGER, INTENT(IN) :: KA, KB, LDAB, &
LDBB, LDX, N
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(OUT) :: RWORK(*)
COMPLEX(wp), INTENT(IN) :: BB(LDBB,*)
COMPLEX(wp), INTENT(INOUT) :: AB(LDAB,*)
COMPLEX(wp), INTENT(OUT) :: WORK(*), &
X(LDX,*)
where
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


LA_SBGST / LA_HBGST reduces a real symmetric / complex Hermitian definite banded generalized eigenproblem $A x = \lambda B x$ to standard form $C y = \lambda y$, such that $C$ has the same bandwidth as $A$.
References: See  [1] and [9,20].
-----------------------------------


next up previous contents index
Next: Computational Routines for the Up: Computational Routines Previous: Computational Routines for the   Contents   Index
Susan Blackford 2001-08-19