Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cgeesx (3p)

Name

cgeesx - genvalues, the Schur form T, and, optionally, the matrix of Schur vec- tors Z

Synopsis

SUBROUTINE CGEESX(JOBZ, SORTEV, SELECT, SENSE, N, A, LDA, NOUT, W, Z,
LDZ, RCONE, RCONV, WORK, LDWORK, WORK2, BWORK3, INFO)

CHARACTER*1 JOBZ, SORTEV, SENSE
COMPLEX A(LDA,*), W(*), Z(LDZ,*), WORK(*)
INTEGER N, LDA, NOUT, LDZ, LDWORK, INFO
LOGICAL SELECT
LOGICAL BWORK3(*)
REAL RCONE, RCONV
REAL WORK2(*)

SUBROUTINE CGEESX_64(JOBZ, SORTEV, SELECT, SENSE, N, A, LDA, NOUT, W,
Z, LDZ, RCONE, RCONV, WORK, LDWORK, WORK2, BWORK3, INFO)

CHARACTER*1 JOBZ, SORTEV, SENSE
COMPLEX A(LDA,*), W(*), Z(LDZ,*), WORK(*)
INTEGER*8 N, LDA, NOUT, LDZ, LDWORK, INFO
LOGICAL*8 SELECT
LOGICAL*8 BWORK3(*)
REAL RCONE, RCONV
REAL WORK2(*)




F95 INTERFACE
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, DIMENSION(:) :: W, WORK
COMPLEX, DIMENSION(:,:) :: A, Z
INTEGER :: N, LDA, NOUT, LDZ, LDWORK, INFO
LOGICAL :: SELECT
LOGICAL, DIMENSION(:) :: BWORK3
REAL :: RCONE, RCONV
REAL, 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, DIMENSION(:) :: W, WORK
COMPLEX, DIMENSION(:,:) :: A, Z
INTEGER(8) :: N, LDA, NOUT, LDZ, LDWORK, INFO
LOGICAL(8) :: SELECT
LOGICAL(8), DIMENSION(:) :: BWORK3
REAL :: RCONE, RCONV
REAL, DIMENSION(:) :: WORK2




C INTERFACE
#include <sunperf.h>

void  cgeesx(char jobz, char sortev, int(*select)(complex), char sense,
int n, complex *a, int lda, int *nout,  complex  *w,  complex
*z, int ldz, float *rcone, float *rconv, int *info);

void  cgeesx_64(char  jobz,  char  sortev, long(*select)(complex), char
sense, long n, complex *a, long lda, long *nout, complex  *w,
complex  *z,  long  ldz,  float  *rcone,  float  *rconv, long
*info);

Description

Oracle Solaris Studio Performance Library                           cgeesx(3P)



NAME
       cgeesx  -  compute for an N-by-N complex nonsymmetric matrix A, the ei-
       genvalues, the Schur form T, and, optionally, the matrix of Schur  vec-
       tors Z


SYNOPSIS
       SUBROUTINE CGEESX(JOBZ, SORTEV, SELECT, SENSE, N, A, LDA, NOUT, W, Z,
             LDZ, RCONE, RCONV, WORK, LDWORK, WORK2, BWORK3, INFO)

       CHARACTER*1 JOBZ, SORTEV, SENSE
       COMPLEX A(LDA,*), W(*), Z(LDZ,*), WORK(*)
       INTEGER N, LDA, NOUT, LDZ, LDWORK, INFO
       LOGICAL SELECT
       LOGICAL BWORK3(*)
       REAL RCONE, RCONV
       REAL WORK2(*)

       SUBROUTINE CGEESX_64(JOBZ, SORTEV, SELECT, SENSE, N, A, LDA, NOUT, W,
             Z, LDZ, RCONE, RCONV, WORK, LDWORK, WORK2, BWORK3, INFO)

       CHARACTER*1 JOBZ, SORTEV, SENSE
       COMPLEX A(LDA,*), W(*), Z(LDZ,*), WORK(*)
       INTEGER*8 N, LDA, NOUT, LDZ, LDWORK, INFO
       LOGICAL*8 SELECT
       LOGICAL*8 BWORK3(*)
       REAL RCONE, RCONV
       REAL WORK2(*)




   F95 INTERFACE
       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, DIMENSION(:) :: W, WORK
       COMPLEX, DIMENSION(:,:) :: A, Z
       INTEGER :: N, LDA, NOUT, LDZ, LDWORK, INFO
       LOGICAL :: SELECT
       LOGICAL, DIMENSION(:) :: BWORK3
       REAL :: RCONE, RCONV
       REAL, 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, DIMENSION(:) :: W, WORK
       COMPLEX, DIMENSION(:,:) :: A, Z
       INTEGER(8) :: N, LDA, NOUT, LDZ, LDWORK, INFO
       LOGICAL(8) :: SELECT
       LOGICAL(8), DIMENSION(:) :: BWORK3
       REAL :: RCONE, RCONV
       REAL, DIMENSION(:) :: WORK2




   C INTERFACE
       #include <sunperf.h>

       void  cgeesx(char jobz, char sortev, int(*select)(complex), char sense,
                 int n, complex *a, int lda, int *nout,  complex  *w,  complex
                 *z, int ldz, float *rcone, float *rconv, int *info);

       void  cgeesx_64(char  jobz,  char  sortev, long(*select)(complex), char
                 sense, long n, complex *a, long lda, long *nout, complex  *w,
                 complex  *z,  long  ldz,  float  *rcone,  float  *rconv, long
                 *info);



PURPOSE
       cgeesx computes for an N-by-N complex nonsymmetric matrix A, the eigen-
       values,  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 quan-
       tities are called s and sep respectively).

       A complex matrix is in Schur form if it is upper triangular.


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  one  COMPLEX  argument  SELECT  must  be
                 declared  EXTERNAL  in  the  calling subroutine.  If SORTEV =
                 'S', SELECT is used to select eigenvalues to order to the top
                 left  of the Schur form.  If SORTEV = 'N', SELECT is not ref-
                 erenced.  An eigenvalue W(j) is selected if  SELECT(W(j))  is
                 true.


       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)
                 COMPLEX  array,  dimension(LDA,N) On entry, the N-by-N matrix
                 A.  On exit, A is overwritten by its 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 for which SELECT is true.


       W (output)
                 COMPLEX array, dimension(N) W contains the computed eigenval-
                 ues, in the same order that they appear on  the  diagonal  of
                 the output Schur form T.


       Z (output)
                 COMPLEX array, dimension(LDZ,N) If JOBZ = 'V', Z contains the
                 unitary 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.


       RCONE (output)
                 If SENSE = 'E' or 'B', RCONE 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)
                 COMPLEX array,  dimension(LDWORK)  On  exit,  if  INFO  =  0,
                 WORK(1) returns the optimal LDWORK.


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


       WORK2 (workspace)
                 REAL array, dimension(N)


       BWORK3 (workspace)
                 LOGICAL array, 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 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.




                                  7 Nov 2015                        cgeesx(3P)