NAME

sgeesx - compute for an N-by-N real nonsymmetric matrix A, the eigenvalues, the real Schur form T, and, optionally, the matrix of Schur vectors Z


SYNOPSIS

  SUBROUTINE SGEESX( JOBZ, SORTEV, SELECT, SENSE, N, A, LDA, NOUT, WR, 
 *      WI, Z, LDZ, SRCONE, RCONV, WORK, LDWORK, IWORK2, LDWRK2, BWORK3, 
 *      INFO)
  CHARACTER * 1 JOBZ, SORTEV, SENSE
  INTEGER N, LDA, NOUT, LDZ, LDWORK, LDWRK2, INFO
  INTEGER IWORK2(*)
  LOGICAL SELECT
  LOGICAL BWORK3(*)
  REAL SRCONE, RCONV
  REAL A(LDA,*), WR(*), WI(*), Z(LDZ,*), WORK(*)
  SUBROUTINE SGEESX_64( JOBZ, SORTEV, SELECT, SENSE, N, A, LDA, NOUT, 
 *      WR, WI, Z, LDZ, SRCONE, RCONV, WORK, LDWORK, IWORK2, LDWRK2, 
 *      BWORK3, INFO)
  CHARACTER * 1 JOBZ, SORTEV, SENSE
  INTEGER*8 N, LDA, NOUT, LDZ, LDWORK, LDWRK2, INFO
  INTEGER*8 IWORK2(*)
  LOGICAL*8 SELECT
  LOGICAL*8 BWORK3(*)
  REAL SRCONE, RCONV
  REAL A(LDA,*), WR(*), WI(*), Z(LDZ,*), WORK(*)

F95 INTERFACE

  SUBROUTINE GEESX( JOBZ, SORTEV, SELECT, SENSE, [N], A, [LDA], NOUT, 
 *       WR, WI, Z, [LDZ], SRCONE, RCONV, [WORK], [LDWORK], [IWORK2], 
 *       [LDWRK2], [BWORK3], [INFO])
  CHARACTER(LEN=1) :: JOBZ, SORTEV, SENSE
  INTEGER :: N, LDA, NOUT, LDZ, LDWORK, LDWRK2, INFO
  INTEGER, DIMENSION(:) :: IWORK2
  LOGICAL :: SELECT
  LOGICAL, DIMENSION(:) :: BWORK3
  REAL :: SRCONE, RCONV
  REAL, DIMENSION(:) :: WR, WI, WORK
  REAL, DIMENSION(:,:) :: A, Z
  SUBROUTINE GEESX_64( JOBZ, SORTEV, SELECT, SENSE, [N], A, [LDA], 
 *       NOUT, WR, WI, Z, [LDZ], SRCONE, RCONV, [WORK], [LDWORK], [IWORK2], 
 *       [LDWRK2], [BWORK3], [INFO])
  CHARACTER(LEN=1) :: JOBZ, SORTEV, SENSE
  INTEGER(8) :: N, LDA, NOUT, LDZ, LDWORK, LDWRK2, INFO
  INTEGER(8), DIMENSION(:) :: IWORK2
  LOGICAL(8) :: SELECT
  LOGICAL(8), DIMENSION(:) :: BWORK3
  REAL :: SRCONE, RCONV
  REAL, DIMENSION(:) :: WR, WI, WORK
  REAL, DIMENSION(:,:) :: A, Z

C INTERFACE

#include <sunperf.h>

void sgeesx(char jobz, char sortev, logical(*select)(float,float), char sense, int n, float *a, int lda, int *nout, float *wr, float *wi, float *z, int ldz, float *srcone, float *rconv, int *info);

void sgeesx_64(char jobz, char sortev, logical(*select)(float,float), char sense, long n, float *a, long lda, long *nout, float *wr, float *wi, float *z, long ldz, float *srcone, float *rconv, long *info);


PURPOSE

sgeesx computes for an N-by-N real nonsymmetric matrix A, the eigenvalues, the real Schur form T, and, optionally, the matrix of Schur vectors Z. This gives the Schur factorization A = Z*T*(Z**T).

Optionally, it also orders the eigenvalues on the diagonal of the real 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 real matrix is in real Schur form if it is upper quasi-triangular with 1-by-1 and 2-by-2 blocks. 2-by-2 blocks will be standardized in the form

          [  a  b  ]
          [  c  a  ]

where b*c < 0. The eigenvalues of such a block are a +- sqrt(bc).


ARGUMENTS