Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cgees (3p)

Name

cgees - values, the Schur form T, and, optionally, the matrix of Schur vectors Z

Synopsis

SUBROUTINE CGEES(JOBZ, SORTEV, SELECT, N, A, LDA, NOUT, W, Z, LDZ,
WORK, LDWORK, WORK2, WORK3, INFO)

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

SUBROUTINE CGEES_64(JOBZ, SORTEV, SELECT, N, A, LDA, NOUT, W, Z, LDZ,
WORK, LDWORK, WORK2, WORK3, INFO)

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




F95 INTERFACE
SUBROUTINE GEES(JOBZ, SORTEV, SELECT, N, A, LDA, NOUT, W, Z, LDZ,
WORK, LDWORK, WORK2, WORK3, INFO)

CHARACTER(LEN=1) :: JOBZ, SORTEV
COMPLEX, DIMENSION(:) :: W, WORK
COMPLEX, DIMENSION(:,:) :: A, Z
INTEGER :: N, LDA, NOUT, LDZ, LDWORK, INFO
LOGICAL :: SELECT
LOGICAL, DIMENSION(:) :: WORK3
REAL, DIMENSION(:) :: WORK2

SUBROUTINE GEES_64(JOBZ, SORTEV, SELECT, N, A, LDA, NOUT, W, Z,
LDZ, WORK, LDWORK, WORK2, WORK3, INFO)

CHARACTER(LEN=1) :: JOBZ, SORTEV
COMPLEX, DIMENSION(:) :: W, WORK
COMPLEX, DIMENSION(:,:) :: A, Z
INTEGER(8) :: N, LDA, NOUT, LDZ, LDWORK, INFO
LOGICAL(8) :: SELECT
LOGICAL(8), DIMENSION(:) :: WORK3
REAL, DIMENSION(:) :: WORK2




C INTERFACE
#include <sunperf.h>

void  cgees(char  jobz, char sortev, int(*select)(complex), int n, com-
plex *a, int lda, int *nout, complex *w, complex *z, int ldz,
int *info);

void  cgees_64(char  jobz, char sortev, long(*select)(complex), long n,
complex *a, long lda, long *nout,  complex  *w,  complex  *z,
long ldz, long *info);

Description

Oracle Solaris Studio Performance Library                            cgees(3P)



NAME
       cgees - compute for an N-by-N complex nonsymmetric matrix A, the eigen-
       values, the Schur form T, and, optionally, the matrix of Schur  vectors
       Z


SYNOPSIS
       SUBROUTINE CGEES(JOBZ, SORTEV, SELECT, N, A, LDA, NOUT, W, Z, LDZ,
             WORK, LDWORK, WORK2, WORK3, INFO)

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

       SUBROUTINE CGEES_64(JOBZ, SORTEV, SELECT, N, A, LDA, NOUT, W, Z, LDZ,
             WORK, LDWORK, WORK2, WORK3, INFO)

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




   F95 INTERFACE
       SUBROUTINE GEES(JOBZ, SORTEV, SELECT, N, A, LDA, NOUT, W, Z, LDZ,
              WORK, LDWORK, WORK2, WORK3, INFO)

       CHARACTER(LEN=1) :: JOBZ, SORTEV
       COMPLEX, DIMENSION(:) :: W, WORK
       COMPLEX, DIMENSION(:,:) :: A, Z
       INTEGER :: N, LDA, NOUT, LDZ, LDWORK, INFO
       LOGICAL :: SELECT
       LOGICAL, DIMENSION(:) :: WORK3
       REAL, DIMENSION(:) :: WORK2

       SUBROUTINE GEES_64(JOBZ, SORTEV, SELECT, N, A, LDA, NOUT, W, Z,
              LDZ, WORK, LDWORK, WORK2, WORK3, INFO)

       CHARACTER(LEN=1) :: JOBZ, SORTEV
       COMPLEX, DIMENSION(:) :: W, WORK
       COMPLEX, DIMENSION(:,:) :: A, Z
       INTEGER(8) :: N, LDA, NOUT, LDZ, LDWORK, INFO
       LOGICAL(8) :: SELECT
       LOGICAL(8), DIMENSION(:) :: WORK3
       REAL, DIMENSION(:) :: WORK2




   C INTERFACE
       #include <sunperf.h>

       void  cgees(char  jobz, char sortev, int(*select)(complex), int n, com-
                 plex *a, int lda, int *nout, complex *w, complex *z, int ldz,
                 int *info);

       void  cgees_64(char  jobz, char sortev, long(*select)(complex), long n,
                 complex *a, long lda, long *nout,  complex  *w,  complex  *z,
                 long ldz, long *info);



PURPOSE
       cgees  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.   The  leading
       columns  of Z then form an orthonormal basis for the invariant subspace
       corresponding to the selected eigenvalues.

       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.  The eigenvalue W(j) is selected if SELECT(W(j))  is
                 true.


       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 has been 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; if JOBZ =
                 'V', LDZ >= N.


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


       LDWORK (input)
                 The  dimension of the array WORK.  LDWORK >= max(1,2*N).  For
                 good performance, LDWORK must generally be larger.

                 If LDWORK = -1, then a workspace query is assumed;  the  rou-
                 tine  only  calculates  the  optimal  size of the WORK array,
                 returns this value as the first entry of the WORK array,  and
                 no error message related to LDWORK is issued by XERBLA.


       WORK2 (workspace)
                 REAL array, dimension(N)


       WORK3 (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  matrix  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 scal-
                 ing.




                                  7 Nov 2015                         cgees(3P)