zgeesx - compute for an N-by-N complex nonsymmetric matrix A, the eigenvalues, the Schur form T, and, optionally, the matrix of Schur vectors Z
SUBROUTINE ZGEESX( JOBZ, SORTEV, SELECT, SENSE, N, A, LDA, NOUT, W, * Z, LDZ, RCONE, RCONV, WORK, LDWORK, WORK2, BWORK3, INFO) CHARACTER * 1 JOBZ, SORTEV, SENSE DOUBLE COMPLEX A(LDA,*), W(*), Z(LDZ,*), WORK(*) INTEGER N, LDA, NOUT, LDZ, LDWORK, INFO LOGICAL SELECT LOGICAL BWORK3(*) DOUBLE PRECISION RCONE, RCONV DOUBLE PRECISION WORK2(*)
SUBROUTINE ZGEESX_64( JOBZ, SORTEV, SELECT, SENSE, N, A, LDA, NOUT, * W, Z, LDZ, RCONE, RCONV, WORK, LDWORK, WORK2, BWORK3, INFO) CHARACTER * 1 JOBZ, SORTEV, SENSE DOUBLE COMPLEX A(LDA,*), W(*), Z(LDZ,*), WORK(*) INTEGER*8 N, LDA, NOUT, LDZ, LDWORK, INFO LOGICAL*8 SELECT LOGICAL*8 BWORK3(*) DOUBLE PRECISION RCONE, RCONV DOUBLE PRECISION WORK2(*)
SUBROUTINE GEESX( JOBZ, SORTEV, SELECT, SENSE, [N], A, [LDA], NOUT, * W, Z, [LDZ], RCONE, RCONV, [WORK], [LDWORK], [WORK2], [BWORK3], * [INFO]) CHARACTER(LEN=1) :: JOBZ, SORTEV, SENSE COMPLEX(8), DIMENSION(:) :: W, WORK COMPLEX(8), DIMENSION(:,:) :: A, Z INTEGER :: N, LDA, NOUT, LDZ, LDWORK, INFO LOGICAL :: SELECT LOGICAL, DIMENSION(:) :: BWORK3 REAL(8) :: RCONE, RCONV REAL(8), DIMENSION(:) :: WORK2
SUBROUTINE GEESX_64( JOBZ, SORTEV, SELECT, SENSE, [N], A, [LDA], * NOUT, W, Z, [LDZ], RCONE, RCONV, [WORK], [LDWORK], [WORK2], * [BWORK3], [INFO]) CHARACTER(LEN=1) :: JOBZ, SORTEV, SENSE COMPLEX(8), DIMENSION(:) :: W, WORK COMPLEX(8), DIMENSION(:,:) :: A, Z INTEGER(8) :: N, LDA, NOUT, LDZ, LDWORK, INFO LOGICAL(8) :: SELECT LOGICAL(8), DIMENSION(:) :: BWORK3 REAL(8) :: RCONE, RCONV REAL(8), DIMENSION(:) :: WORK2
#include <sunperf.h>
void zgeesx(char jobz, char sortev, logical(*select)(COMPLEX*16), char sense, int n, doublecomplex *a, int lda, int *nout, doublecomplex *w, doublecomplex *z, int ldz, double *rcone, double *rconv, int *info);
void zgeesx_64(char jobz, char sortev, logical(*select)(COMPLEX*16), char sense, long n, doublecomplex *a, long lda, long *nout, doublecomplex *w, doublecomplex *z, long ldz, double *rcone, double *rconv, long *info);
zgeesx computes for an N-by-N complex nonsymmetric matrix A, the eigenvalues, the Schur form T, and, optionally, the matrix of Schur vectors Z. This gives the Schur factorization A = Z*T*(Z**H).
Optionally, it also orders the eigenvalues on the diagonal of the Schur form so that selected eigenvalues are at the top left; computes a reciprocal condition number for the average of the selected eigenvalues (RCONDE); and computes a reciprocal condition number for the right invariant subspace corresponding to the selected eigenvalues (RCONDV). The leading columns of Z form an orthonormal basis for this invariant subspace.
For further explanation of the reciprocal condition numbers RCONDE and RCONDV, see Section 4.10 of the LAPACK Users' Guide (where these quantities are called s and sep respectively).
A complex matrix is in Schur form if it is upper triangular.
= 'N': Schur vectors are not computed;
= 'V': Schur vectors are computed.
= 'S': Eigenvalues are ordered (see SELECT).
W(j)
is selected if SELECT(W(j))
is true.
= 'E': Computed for average of selected eigenvalues only;
= 'V': Computed for selected right invariant subspace only;
= 'B': Computed for both. If SENSE = 'E', 'V' or 'B', SORTEV must equal 'S'.
dimension(LDWORK)
On exit, if INFO = 0, WORK(1)
returns the optimal LDWORK.
dimension(N)
dimension(N)
Not referenced if SORTEV = 'N'.
= 0: successful exit
< 0: if INFO = -i, the i-th argument had an illegal value.
> 0: if INFO = i, and i is
< = N: the QR algorithm failed to compute all the
eigenvalues; elements 1:ILO-1 and i+1:N of W contain those eigenvalues which have converged; if JOBZ = 'V', Z contains the transformation which reduces A to its partially converged Schur form. = N+1: the eigenvalues could not be reordered because some eigenvalues were too close to separate (the problem is very ill-conditioned); = N+2: after reordering, roundoff changed values of some complex eigenvalues so that leading eigenvalues in the Schur form no longer satisfy SELECT =.TRUE. This could also be caused by underflow due to scaling.