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


Computational Routines for the Nonsymmetric eigenproblem

LA_GEHRD
Real and complex versions.


SUBROUTINE LA_GEHRD( N, ILO, IHI, A, & 

LDA, TAU, WORK, LWORK, INFO )
INTEGER, INTENT(IN) :: IHI, ILO, LDA, &
LWORK, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(INOUT) :: A(LDA,*)
type(wp), INTENT(OUT) :: TAU(*),
WORK(LWORK)
where
type ::= REAL $\mid$ COMPLEX
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


LA_GEHRD reduces a real / complex general matrix $A$ to upper Hessenberg form $H$ by an orthogonal / unitary similarity transformation: $Q^H A Q = H$ .
References: See  [1] and [9,20].
-----------------------------------

LA_GEBAL
Real and complex versions.


SUBROUTINE LA_GEBAL( JOB, N, A, LDA, & 

ILO, IHI, SCALE, INFO )
CHARACTER(LEN=1), INTENT(IN) :: JOB
INTEGER, INTENT(IN) :: LDA, N
INTEGER, INTENT(OUT) :: IHI, ILO, INFO
REAL(wp), INTENT(OUT) :: SCALE(*)
type(wp), INTENT(INOUT) :: A(LDA,*)
where
type ::= REAL $\mid$ COMPLEX
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


LA_GEBAL balances a general real / complex matrix $A$.
References: See  [1] and [9,20,37].
-----------------------------------

LA_GEBAK
Real and complex versions.


SUBROUTINE LA_GEBAK( JOB, SIDE, N, ILO, & 

IHI, SCALE, M, V, LDV, INFO )
CHARACTER(LEN=1), INTENT(IN) :: JOB, &
SIDE
INTEGER, INTENT(IN) :: IHI, ILO, LDV, M, N
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(IN) :: SCALE(*)
type(wp), INTENT(INOUT) :: V(LDV,*)
where
type ::= REAL $\mid$ COMPLEX
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


LA_GEBAK forms the right or left eigenvectors of a real / complex general matrix by backward transformation on the computed eigenvectors of the balanced matrix output by LA_GEBAL.
References: See  [1] and [9,20].
-----------------------------------

LA_ORGHR / LA_UNGHR
Real and complex versions.


SUBROUTINE LA_ORGHR / LA_UNGHR( N, & 

ILO, IHI, A, LDA, TAU, WORK, LWORK, &
INFO )
INTEGER, INTENT(IN) :: IHI, ILO, LDA, &
LWORK, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(IN) :: TAU(*)
type(wp), INTENT(INOUT) :: A(LDA,*)
type(wp), INTENT(OUT) :: WORK(LWORK)
where
type ::= REAL $\mid$ COMPLEX
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


LA_ORGHR / LA_UNGHR generate a real orthogonal / complex unitary matrix $Q$ which is defined as the product of elementary reflectors of order $n$, as returned by LA_GEHRD.
References: See  [1] and [9,20].
-----------------------------------

LA_ORMHR / LA_UNMHR
Real and complex versions.


SUBROUTINE LA_ORMHR / LA_UNMHR( SIDE, & 

TRANS, M, N, ILO, IHI, A, LDA, TAU, C, &
LDC, WORK, LWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: SIDE, &
TRANS
INTEGER, INTENT(IN) :: IHI, ILO, LDA, LDC, &
LWORK, M, N
INTEGER, INTENT(OUT) :: INFO
type(wp), INTENT(IN) :: A(LDA,*), TAU(*)
type(wp), INTENT(INOUT) :: C(LDA,*)
type(wp), INTENT(OUT) :: WORK(LWORK)
where
type ::= REAL $\mid$ COMPLEX
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


LA_ORMHR / LA_UNMHR overwrites the general real / complex $m \times n$ $C$ with a real orthogonal / complex unitary matrix $Q$ of order $nq$ where $Q$ is defined as the product of elementary reflectors, as returned by LA_GEHRD.
References: See  [1] and [9,20].
-----------------------------------

LA_HSEQR
Real version.


SUBROUTINE LA_HSEQR( JOB, COMPZ, N, & 

ILO, IHI, H, LDH, WR, WI, Z, LDZ, WORK, &
LWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: COMPZ, &
JOB
INTEGER, INTENT(IN) :: IHI, ILO, LDH, LDZ,
LWORK, N
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(OUT) :: WR(*), WI(*)
REAL(wp), INTENT(INOUT) :: H(LDH,*), Z(LDZ,*)
REAL(wp), INTENT(OUT) :: WORK(LWORK)
where
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


Complex version.


 SUBROUTINE LA_HSEQR( JOB, COMPZ, N, & 

ILO, IHI, H, LDH, W, Z, LDZ, WORK, &
LWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: COMPZ, &
JOB
INTEGER, INTENT(IN) :: IHI, ILO, LDH, LDZ, &
LWORK, N
INTEGER, INTENT(OUT) :: INFO
COMPLEX(wp), INTENT(INOUT) :: H(LDH,*), &
Z(LDZ,*)
COMPLEX(wp), INTENT(OUT) :: W(*), &
WORK(LWORK)
where
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


LA_HSEQR computes the eigenvalues of a real / complex upper Hessenberg matrix $H$, and, optionally, the matrices $T$ and $Z$ from the Schur decomposition $H = Z T Z^H$, where $T$ is an upper triangular matrix (the Schur form), and $Z$ is the unitary matrix of Schur vectors.

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

LA_HSEIN
Real version.


SUBROUTINE LA_HSEIN( VR, LDVR, MM, M, & 

WORK, IFAILL, IFAILR, INFO )
CHARACTER(LEN=1), INTENT(IN) :: &
EIGSRC, INITV, SIDE
INTEGER, INTENT(IN) :: LDH, LDVL, LDVR, &
MM, N
INTEGER, INTENT(OUT) :: INFO, M, &
IFAILL(*), IFAILR(*)
LOGICAL, INTENT(IN) :: SELECT(*)
REAL(wp), INTENT(INOUT) :: WR(*), WI(*)
REAL(wp), INTENT(IN) :: H(LDH,*)
REAL(wp), INTENT(INOUT) :: VL(LDVL,*),
VR(LDVR,*)
REAL(wp), INTENT(OUT) :: WORK(*)
where
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


Complex version.


 SUBROUTINE LA_HSEIN( VR, LDVR, MM, M, & 

WORK, RWORK, IFAILL, IFAILR, INFO )
CHARACTER(LEN=1), INTENT(IN) :: &
EIGSRC, INITV, SIDE
INTEGER, INTENT(IN) :: LDH, LDVL, LDVR, &
MM, N
INTEGER, INTENT(OUT) :: INFO, M, &
IFAILL(*), IFAILR(*)
LOGICAL, INTENT(IN) :: SELECT(*)
REAL(wp), INTENT(OUT) :: RWORK( * )
COMPLEX(wp), INTENT(IN) :: H(LDH,*)
COMPLEX(wp), INTENT(INOUT) :: VL(LDVL,*), &
VR(LDVR,*), W(*)
COMPLEX(wp), INTENT(OUT) :: WORK(*)
where
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


LA_HSEIN uses inverse iteration to find specified right and/or left eigenvectors of a real / complex upper Hessenberg matrix $H$.
References: See  [1] and [9,20].
-----------------------------------

LA_TREVC
Real version.


SUBROUTINE LA_TREVC( SIDE, HOWMNY, & 

SELECT, N, T, LDT, VL, LDVL, VR, LDVR, &
MM, M, WORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: &
HOWMNY, SIDE
INTEGER, INTENT(IN) :: LDT, LDVL, LDVR, &
MM, N
INTEGER, INTENT(OUT) :: INFO, M
LOGICAL, INTENT(INOUT) :: SELECT(*)
REAL(wp), INTENT(IN) :: T(LDT,*)
REAL(wp), INTENT(INOUT) :: VL(LDVL,*), &
VR(LDVR,*)
REAL(wp), INTENT(OUT) :: WORK(*)
where
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


Complex version.


 SUBROUTINE LA_TREVC( SIDE, HOWMNY, & 

SELECT, N, T, LDT, VL, LDVL, VR, LDVR, &
MM, M, WORK, RWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: &
HOWMNY, SIDE
INTEGER, INTENT(IN) :: LDT, LDVL, LDVR, &
MM, N
INTEGER, INTENT(OUT) :: INFO, M
LOGICAL, INTENT(INOUT) :: SELECT(*)
REAL(wp), INTENT(OUT) :: RWORK(*)
COMPLEX(wp), INTENT(INOUT) :: T(LDT,*), &
VL(LDVL,*), VR(LDVR,*)
COMPLEX(wp), INTENT(OUT) :: WORK(*)
where
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


LA_TREVC computes some or all of the right and/or left eigenvectors of a real / complex upper quasi-triangular / triangular matrix $T$.
References: See  [1] and [9,20].
-----------------------------------

LA_TREXC
Real version.


SUBROUTINE LA_TREXC( COMPQ, N, T, LDT, & 

Q, LDQ, IFST, ILST, WORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: COMPQ
INTEGER, INTENT(IN) :: IFST, ILST, LDQ, &
LDT, N
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(INOUT) :: Q(LDQ,*), &
T(LDT,*), WORK(*)
where
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


Complex version.


 SUBROUTINE LA_TREXC( COMPQ, N, T, LDT, & 

Q, LDQ, IFST, ILST, INFO )
CHARACTER(LEN=1), INTENT(IN) :: COMPQ
INTEGER, INTENT(IN) :: IFST, ILST, LDQ, &
LDT, N
INTEGER, INTENT(OUT) :: INFO
COMPLEX(wp), INTENT(INOUT) :: Q(LDQ,*), &
T(LDT,*)
where
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


LA_TREXC reorders the Schur factorization of a real / complex matrix $A = Q T Q^H$, so that the diagonal block of $T$ with row index IFST is moved to row ILST.
References: See  [1] and [9,20].
-----------------------------------

LA_TRSYL
Real and complex versions.


SUBROUTINE LA_TRSYL( TRANA, TRANB, & 

ISGN, M, N, A, LDA, B, LDB, C, LDC, &
SCALE, INFO )
CHARACTER(LEN=1), INTENT(IN) :: &
TRANA, TRANB
INTEGER, INTENT(IN) :: ISGN, LDA, LDB, &
LDC, M, N
INTEGER, INTENT(OUT) :: INFO
REAL(wp), INTENT(OUT) :: SCALE
type(wp), INTENT(IN) :: A(LDA,*), B(LDB,*)
type(wp), INTENT(INOUT) :: C(LDC,*)
where
type ::= REAL $\mid$ COMPLEX
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


LA_TRSYL solves the real / complex Sylvester matrix equation.
References: See  [1] and [9,20].
-----------------------------------

LA_TRSNA
Real version.


SUBROUTINE LA_TRSNA( JOB, HOWMNY, & 

SELECT, N, T, LDT, VL, LDVL, VR, LDVR, &
S, SEP, MM, M, WORK, LDWORK, IWORK, &
INFO )
CHARACTER(LEN=1), INTENT(IN) :: &
HOWMNY, JOB
INTEGER, INTENT(IN) :: LDT, LDVL, LDVR, &
LDWORK, MM, N
INTEGER, INTENT(OUT) :: INFO, M, IWORK(*)
LOGICAL, INTENT(IN) :: SELECT(*)
REAL(wp), INTENT(OUT) :: S(*), SEP(*)
REAL(wp), INTENT(IN) :: T(LDT,*), &
VL(LDVL,*), VR(LDVR,*)
REAL(wp), INTENT(OUT) :: WORK(LDWORK,*)
where
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


Complex version.


 SUBROUTINE LA_TRSNA( JOB, HOWMNY, & 

SELECT, N, T, LDT, VL, LDVL, VR, LDVR, &
S, SEP, MM, M, WORK, LDWORK, RWORK, &
INFO )
CHARACTER(LEN=1), INTENT(IN) :: &
HOWMNY, JOB
INTEGER, INTENT(IN) :: LDT, LDVL, LDVR, &
LDWORK, MM, N
INTEGER, INTENT(OUT) :: INFO, M
LOGICAL, INTENT(IN) :: SELECT(*)
REAL(wp), INTENT(OUT) :: RWORK(*), S(*), &
SEP(*)
COMPLEX(wp), INTENT(IN) :: T(LDT,*), &
VL(LDVL,*), VR(LDVR,*)
COMPLEX(wp), INTENT(OUT) :: &
WORK(LDWORK,*)
where
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


LA_TRSNA estimates reciprocal condition numbers for specified eigenvalues and/or right eigenvectors of a real / complex upper quasi-triangular / triangular matrix $T$ (or of any matrix $Q T Q^H$ with $Q$ orthogonal / unitary).
References: See  [1] and [9,20].
-----------------------------------

LA_TRSEN
Real version.


SUBROUTINE LA_TRSEN( JOB, COMPQ, & 

SELECT, N, T, LDT, Q, LDQ, WR, WI, M, S, &
SEP, WORK, LWORK, IWORK, LIWORK, &
INFO )
CHARACTER(LEN=1), INTENT(IN) :: COMPQ, &
JOB
INTEGER, INTENT(IN) :: LDQ, LDT, LWORK, &
N, LIWORK
INTEGER, INTENT(OUT) :: INFO, M, &
IWORK(LIWORK)
REAL(wp), INTENT(OUT) :: S, SEP
LOGICAL, INTENT(IN) :: SELECT(*)
REAL(wp), INTENT(INOUT) :: Q(LDQ,*), T(LDT,*)
REAL(wp), INTENT(IN) :: WR(*), WI(*)
REAL(wp), INTENT(OUT) :: WORK(LWORK)
where
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


Complex version.


 SUBROUTINE LA_TRSEN( JOB, COMPQ, & 

SELECT, N, T, LDT, Q, LDQ, W, M, S, &
SEP, WORK, LWORK, INFO )
CHARACTER(LEN=1), INTENT(IN) :: COMPQ, &
JOB
INTEGER, INTENT(IN) :: LDQ, LDT, LWORK, N
INTEGER, INTENT(OUT) :: INFO, M
REAL(wp), INTENT(OUT) :: S, SEP
LOGICAL, INTENT(IN) :: SELECT(*)
COMPLEX(wp), INTENT(INOUT) :: Q(LDQ,*), &
T(LDT,*)
COMPLEX(wp), INTENT(IN) :: W(*), &
WORK(LWORK)
where
wp ::= KIND(1.0) $\mid$ KIND(1.0D0)


LA_TRSEN reorders the Schur factorization of a real / complex matrix $A = Q T Q^H$, so that a selected cluster of eigenvalues appears in the leading positions on the diagonal of the upper triangular matrix $T$, and the leading columns of $Q$ form an orthonormal basis of the corresponding right invariant subspace.
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