Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

sgeesx (3p)

Name

sgeesx - values, 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, int(*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, long(*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);

Description

Oracle Solaris Studio Performance Library                           sgeesx(3P)



NAME
       sgeesx  -  compute for an N-by-N real nonsymmetric matrix A, the eigen-
       values, 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, int(*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, long(*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 eigenval-
       ues, the real Schur form T, and, optionally, the matrix of  Schur  vec-
       tors 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  quan-
       tities 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
       JOBZ (input)
                 = 'N': Schur vectors are not computed;
                 = 'V': Schur vectors are computed.


       SORTEV (input)
                 Specifies  whether  or  not  to  order the eigenvalues on the
                 diagonal of the Schur  form.   =  'N':  Eigenvalues  are  not
                 ordered;
                 = 'S': Eigenvalues are ordered (see SELECT).


       SELECT (input)
                 LOGICAL  FUNCTION  of  two  REAL  arguments  SELECT  must  be
                 declared EXTERNAL in the calling  subroutine.   If  SORTEV  =
                 'S',  SELECT is used to select eigenvalues to sort to the top
                 left of the Schur form.  If SORTEV = 'N', SELECT is not  ref-
                 erenced.   An  eigenvalue WR(j)+sqrt(-1)*WI(j) is selected if
                 SELECT(WR(j),WI(j)) is true; i.e., if either one of a complex
                 conjugate  pair  of  eigenvalues  is selected, then both are.
                 Note that a selected complex eigenvalue may no longer satisfy
                 SELECT(WR(j),WI(j))  =  .TRUE. after ordering, since ordering
                 may change the value of complex  eigenvalues  (especially  if
                 the  eigenvalue is ill-conditioned); in this case INFO may be
                 set to N+3 (see INFO below).


       SENSE (input)
                 Determines which reciprocal condition numbers  are  computed.
                 = 'N': None are computed;
                 = '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'.


       N (input) The order of the matrix A. N >= 0.


       A (input/output)
                 REAL array, dimension (LDA,N) On entry, the N-by-N matrix  A.
                 On exit, A is overwritten by its real Schur form T.


       LDA (input)
                 The leading dimension of the array A.  LDA >= max(1,N).


       NOUT (output)
                 If SORTEV = 'N', NOUT = 0.  If SORTEV = 'S', NOUT = number of
                 eigenvalues (after sorting) for which SELECT is  true.  (Com-
                 plex  conjugate pairs for which SELECT is true for either ei-
                 genvalue count as 2.)


       WR (output)
                 WR and WI contain the real and imaginary parts, respectively,
                 of  the  computed  eigenvalues,  in  the same order that they
                 appear on the diagonal of the output Schur form  T.   Complex
                 conjugate  pairs of eigenvalues appear consecutively with the
                 eigenvalue having the positive imaginary part first.


       WI (output)
                 See the description for WR.


       Z (output)
                 If JOBZ = 'V', Z contains the orthogonal matrix  Z  of  Schur
                 vectors.  If JOBZ = 'N', Z is not referenced.


       LDZ (input)
                 The  leading dimension of the array Z.  LDZ >= 1, and if JOBZ
                 = 'V', LDZ >= N.


       SRCONE (output)
                 If SENSE = 'E' or 'B', SRCONE contains the reciprocal  condi-
                 tion number for the average of the selected eigenvalues.  Not
                 referenced if SENSE = 'N' or 'V'.


       RCONV (output)
                 If SENSE = 'V' or 'B', RCONV contains the  reciprocal  condi-
                 tion  number  for the selected right invariant subspace.  Not
                 referenced if SENSE = 'N' or 'E'.


       WORK (workspace)
                 On exit, if INFO = 0, WORK(1) returns the optimal LDWORK.


       LDWORK (input)
                 The dimension of  the  array  WORK.   LDWORK  >=  max(1,3*N).
                 Also,  if  SENSE  = 'E' or 'V' or 'B', LDWORK >= N+2*NOUT*(N-
                 NOUT), where NOUT is the number of selected eigenvalues  com-
                 puted  by  this  routine.   Note  that  N+2*NOUT*(N-NOUT)  <=
                 N+N*N/2.  For good  performance,  LDWORK  must  generally  be
                 larger.


       IWORK2 (workspace/output)
                 Not  referenced if SENSE = 'N' or 'E'.  On exit, if INFO = 0,
                 IWORK2(1) returns the optimal LDWRK2.


       LDWRK2 (input)
                 The dimension of the array IWORK2.  LDWRK2 >= 1; if  SENSE  =
                 'V' or 'B', LDWRK2 >= NOUT*(N-NOUT).


       BWORK3 (workspace)
                 dimension(N) Not referenced if SORTEV = 'N'.


       INFO (output)
                 = 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 WR and WI contain
                 those eigenvalues which have converged; if JOBZ = 'V', Z con-
                 tains  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  reorder-
                 ing,  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.




                                  7 Nov 2015                        sgeesx(3P)