ztgevc - compute the right and/or left generalized eigenvectors of a pair of complex upper triangular matrices with real diagonal elements (A,B) obtained from the generalized Schur factorization of an original pair of complex nonsymmetric matrices (AO,BO)
SUBROUTINE ZTGEVC(SIDE, HOWMNY, SELECT, N, A, LDA, B, LDB, VL, LDVL, VR, LDVR, MM, M, WORK, RWORK, INFO) CHARACTER*1 SIDE, HOWMNY DOUBLE COMPLEX A(LDA,*), B(LDB,*), VL(LDVL,*), VR(LDVR,*), WORK(*) INTEGER N, LDA, LDB, LDVL, LDVR, MM, M, INFO LOGICAL SELECT(*) DOUBLE PRECISION RWORK(*) SUBROUTINE ZTGEVC_64(SIDE, HOWMNY, SELECT, N, A, LDA, B, LDB, VL, LDVL, VR, LDVR, MM, M, WORK, RWORK, INFO) CHARACTER*1 SIDE, HOWMNY DOUBLE COMPLEX A(LDA,*), B(LDB,*), VL(LDVL,*), VR(LDVR,*), WORK(*) INTEGER*8 N, LDA, LDB, LDVL, LDVR, MM, M, INFO LOGICAL*8 SELECT(*) DOUBLE PRECISION RWORK(*) F95 INTERFACE SUBROUTINE TGEVC(SIDE, HOWMNY, SELECT, N, A, LDA, B, LDB, VL, LDVL, VR, LDVR, MM, M, WORK, RWORK, INFO) CHARACTER(LEN=1) :: SIDE, HOWMNY COMPLEX(8), DIMENSION(:) :: WORK COMPLEX(8), DIMENSION(:,:) :: A, B, VL, VR INTEGER :: N, LDA, LDB, LDVL, LDVR, MM, M, INFO LOGICAL, DIMENSION(:) :: SELECT REAL(8), DIMENSION(:) :: RWORK SUBROUTINE TGEVC_64(SIDE, HOWMNY, SELECT, N, A, LDA, B, LDB, VL, LDVL, VR, LDVR, MM, M, WORK, RWORK, INFO) CHARACTER(LEN=1) :: SIDE, HOWMNY COMPLEX(8), DIMENSION(:) :: WORK COMPLEX(8), DIMENSION(:,:) :: A, B, VL, VR INTEGER(8) :: N, LDA, LDB, LDVL, LDVR, MM, M, INFO LOGICAL(8), DIMENSION(:) :: SELECT REAL(8), DIMENSION(:) :: RWORK C INTERFACE #include <sunperf.h> void ztgevc(char side, char howmny, int *select, int n, doublecomplex *a, int lda, doublecomplex *b, int ldb, doublecomplex *vl, int ldvl, doublecomplex *vr, int ldvr, int mm, int *m, int *info); void ztgevc_64(char side, char howmny, long *select, long n, doublecom- plex *a, long lda, doublecomplex *b, long ldb, doublecomplex *vl, long ldvl, doublecomplex *vr, long ldvr, long mm, long *m, long *info);
Oracle Solaris Studio Performance Library ztgevc(3P)
NAME
ztgevc - compute the right and/or left generalized eigenvectors of a
pair of complex upper triangular matrices with real diagonal elements
(A,B) obtained from the generalized Schur factorization of an original
pair of complex nonsymmetric matrices (AO,BO)
SYNOPSIS
SUBROUTINE ZTGEVC(SIDE, HOWMNY, SELECT, N, A, LDA, B, LDB, VL, LDVL,
VR, LDVR, MM, M, WORK, RWORK, INFO)
CHARACTER*1 SIDE, HOWMNY
DOUBLE COMPLEX A(LDA,*), B(LDB,*), VL(LDVL,*), VR(LDVR,*), WORK(*)
INTEGER N, LDA, LDB, LDVL, LDVR, MM, M, INFO
LOGICAL SELECT(*)
DOUBLE PRECISION RWORK(*)
SUBROUTINE ZTGEVC_64(SIDE, HOWMNY, SELECT, N, A, LDA, B, LDB, VL,
LDVL, VR, LDVR, MM, M, WORK, RWORK, INFO)
CHARACTER*1 SIDE, HOWMNY
DOUBLE COMPLEX A(LDA,*), B(LDB,*), VL(LDVL,*), VR(LDVR,*), WORK(*)
INTEGER*8 N, LDA, LDB, LDVL, LDVR, MM, M, INFO
LOGICAL*8 SELECT(*)
DOUBLE PRECISION RWORK(*)
F95 INTERFACE
SUBROUTINE TGEVC(SIDE, HOWMNY, SELECT, N, A, LDA, B, LDB, VL,
LDVL, VR, LDVR, MM, M, WORK, RWORK, INFO)
CHARACTER(LEN=1) :: SIDE, HOWMNY
COMPLEX(8), DIMENSION(:) :: WORK
COMPLEX(8), DIMENSION(:,:) :: A, B, VL, VR
INTEGER :: N, LDA, LDB, LDVL, LDVR, MM, M, INFO
LOGICAL, DIMENSION(:) :: SELECT
REAL(8), DIMENSION(:) :: RWORK
SUBROUTINE TGEVC_64(SIDE, HOWMNY, SELECT, N, A, LDA, B, LDB,
VL, LDVL, VR, LDVR, MM, M, WORK, RWORK, INFO)
CHARACTER(LEN=1) :: SIDE, HOWMNY
COMPLEX(8), DIMENSION(:) :: WORK
COMPLEX(8), DIMENSION(:,:) :: A, B, VL, VR
INTEGER(8) :: N, LDA, LDB, LDVL, LDVR, MM, M, INFO
LOGICAL(8), DIMENSION(:) :: SELECT
REAL(8), DIMENSION(:) :: RWORK
C INTERFACE
#include <sunperf.h>
void ztgevc(char side, char howmny, int *select, int n, doublecomplex
*a, int lda, doublecomplex *b, int ldb, doublecomplex *vl,
int ldvl, doublecomplex *vr, int ldvr, int mm, int *m, int
*info);
void ztgevc_64(char side, char howmny, long *select, long n, doublecom-
plex *a, long lda, doublecomplex *b, long ldb, doublecomplex
*vl, long ldvl, doublecomplex *vr, long ldvr, long mm, long
*m, long *info);
PURPOSE
ztgevc computes some or all of the right and/or left generalized eigen-
vectors of a pair of complex upper triangular matrices (A,B) that was
obtained from from the generalized Schur factorization of an original
pair of complex nonsymmetric matrices (AO,BO). A and B are upper tri-
angular matrices and B must have real diagonal elements.
The right generalized eigenvector x and the left generalized eigenvec-
tor y of (A,B) corresponding to a generalized eigenvalue w are defined
by:
(A - wB) * x = 0 and y**H * (A - wB) = 0
where y**H denotes the conjugate tranpose of y.
If an eigenvalue w is determined by zero diagonal elements of both A
and B, a unit vector is returned as the corresponding eigenvector.
If all eigenvectors are requested, the routine may either return the
matrices X and/or Y of right or left eigenvectors of (A,B), or the
products Z*X and/or Q*Y, where Z and Q are input unitary matrices. If
(A,B) was obtained from the generalized Schur factorization of an orig-
inal pair of matrices
(A0,B0) = (Q*A*Z**H,Q*B*Z**H),
then Z*X and Q*Y are the matrices of right or left eigenvectors of A.
ARGUMENTS
SIDE (input)
= 'R': compute right eigenvectors only;
= 'L': compute left eigenvectors only;
= 'B': compute both right and left eigenvectors.
HOWMNY (input)
= 'A': compute all right and/or left eigenvectors;
= 'B': compute all right and/or left eigenvectors, and back-
transform them using the input matrices supplied in VR and/or
VL; = 'S': compute selected right and/or left eigenvectors,
specified by the logical array SELECT.
SELECT (input)
If HOWMNY='S', SELECT specifies the eigenvectors to be com-
puted. If HOWMNY='A' or 'B', SELECT is not referenced. To
select the eigenvector corresponding to the j-th eigenvalue,
SELECT(j) must be set to .TRUE..
N (input) The order of the matrices A and B. N >= 0.
A (input) The upper triangular matrix A.
LDA (input)
The leading dimension of array A. LDA >= max(1,N).
B (input) The upper triangular matrix B. B must have real diagonal
elements.
LDB (input)
The leading dimension of array B. LDB >= max(1,N).
VL (input/output)
On entry, if SIDE = 'L' or 'B' and HOWMNY = 'B', VL must con-
tain an N-by-N matrix Q (usually the unitary matrix Q of left
Schur vectors returned by ZHGEQZ). On exit, if SIDE = 'L' or
'B', VL contains: if HOWMNY = 'A', the matrix Y of left
eigenvectors of (A,B); if HOWMNY = 'B', the matrix Q*Y; if
HOWMNY = 'S', the left eigenvectors of (A,B) specified by
SELECT, stored consecutively in the columns of VL, in the
same order as their eigenvalues. If SIDE = 'R', VL is not
referenced.
LDVL (input)
The leading dimension of array VL. LDVL >= max(1,N) if SIDE
= 'L' or 'B'; LDVL >= 1 otherwise.
VR (input/output)
On entry, if SIDE = 'R' or 'B' and HOWMNY = 'B', VR must con-
tain an N-by-N matrix Q (usually the unitary matrix Z of
right Schur vectors returned by ZHGEQZ). On exit, if SIDE =
'R' or 'B', VR contains: if HOWMNY = 'A', the matrix X of
right eigenvectors of (A,B); if HOWMNY = 'B', the matrix Z*X;
if HOWMNY = 'S', the right eigenvectors of (A,B) specified by
SELECT, stored consecutively in the columns of VR, in the
same order as their eigenvalues. If SIDE = 'L', VR is not
referenced.
LDVR (input)
The leading dimension of the array VR. LDVR >= max(1,N) if
SIDE = 'R' or 'B'; LDVR >= 1 otherwise.
MM (input)
The number of columns in the arrays VL and/or VR. MM >= M.
M (output)
The number of columns in the arrays VL and/or VR actually
used to store the eigenvectors. If HOWMNY = 'A' or 'B', M is
set to N. Each selected eigenvector occupies one column.
WORK (workspace)
dimension(2*N)
RWORK (workspace)
dimension(2*N)
INFO (output)
= 0: successful exit.
< 0: if INFO = -i, the i-th argument had an illegal value.
7 Nov 2015 ztgevc(3P)