1ZGEESX(1)             LAPACK driver routine (version 3.2)            ZGEESX(1)
2
3
4

NAME

6       ZGEESX  - computes for an N-by-N complex nonsymmetric matrix A, the ei‐
7       genvalues, the Schur form T, and, optionally, the matrix of Schur  vec‐
8       tors Z
9

SYNOPSIS

11       SUBROUTINE ZGEESX( JOBVS,  SORT, SELECT, SENSE, N, A, LDA, SDIM, W, VS,
12                          LDVS, RCONDE, RCONDV,  WORK,  LWORK,  RWORK,  BWORK,
13                          INFO )
14
15           CHARACTER      JOBVS, SENSE, SORT
16
17           INTEGER        INFO, LDA, LDVS, LWORK, N, SDIM
18
19           DOUBLE         PRECISION RCONDE, RCONDV
20
21           LOGICAL        BWORK( * )
22
23           DOUBLE         PRECISION RWORK( * )
24
25           COMPLEX*16     A( LDA, * ), VS( LDVS, * ), W( * ), WORK( * )
26
27           LOGICAL        SELECT
28
29           EXTERNAL       SELECT
30

PURPOSE

32       ZGEESX computes for an N-by-N complex nonsymmetric matrix A, the eigen‐
33       values, the Schur form T, and, optionally, the matrix of Schur  vectors
34       Z.   This gives the Schur factorization A = Z*T*(Z**H).  Optionally, it
35       also orders the eigenvalues on the diagonal of the Schur form  so  that
36       selected  eigenvalues are at the top left; computes a reciprocal condi‐
37       tion number for the average of the selected eigenvalues  (RCONDE);  and
38       computes a reciprocal condition number for the right invariant subspace
39       corresponding to the selected eigenvalues (RCONDV).  The  leading  col‐
40       umns of Z form an orthonormal basis for this invariant subspace.
41       For  further explanation of the reciprocal condition numbers RCONDE and
42       RCONDV, see Section 4.10 of the LAPACK Users' Guide (where these  quan‐
43       tities are called s and sep respectively).
44       A complex matrix is in Schur form if it is upper triangular.
45

ARGUMENTS

47       JOBVS   (input) CHARACTER*1
48               = 'N': Schur vectors are not computed;
49               = 'V': Schur vectors are computed.
50
51       SORT    (input) CHARACTER*1
52               Specifies whether or not to order the eigenvalues on the diago‐
53               nal of the Schur form.  = 'N': Eigenvalues are not ordered;
54               = 'S': Eigenvalues are ordered (see SELECT).
55
56       SELECT  (external procedure) LOGICAL FUNCTION of one  COMPLEX*16  argu‐
57       ment
58               SELECT must be declared EXTERNAL in the calling subroutine.  If
59               SORT = 'S', SELECT is used to select eigenvalues  to  order  to
60               the  top  left of the Schur form.  If SORT = 'N', SELECT is not
61               referenced.  An eigenvalue W(j) is selected if SELECT(W(j))  is
62               true.
63
64       SENSE   (input) CHARACTER*1
65               Determines  which reciprocal condition numbers are computed.  =
66               'N': None are computed;
67               = 'E': Computed for average of selected eigenvalues only;
68               = 'V': Computed for selected right invariant subspace only;
69               = 'B': Computed for both.  If SENSE = 'E',  'V'  or  'B',  SORT
70               must equal 'S'.
71
72       N       (input) INTEGER
73               The order of the matrix A. N >= 0.
74
75       A       (input/output) COMPLEX*16 array, dimension (LDA, N)
76               On  entry,  the  N-by-N matrix A.  On exit, A is overwritten by
77               its Schur form T.
78
79       LDA     (input) INTEGER
80               The leading dimension of the array A.  LDA >= max(1,N).
81
82       SDIM    (output) INTEGER
83               If SORT = 'N', SDIM = 0.  If SORT = 'S', SDIM = number  of  ei‐
84               genvalues for which SELECT is true.
85
86       W       (output) COMPLEX*16 array, dimension (N)
87               W  contains  the  computed  eigenvalues, in the same order that
88               they appear on the diagonal of the output Schur form T.
89
90       VS      (output) COMPLEX*16 array, dimension (LDVS,N)
91               If JOBVS = 'V', VS contains the unitary matrix Z of Schur  vec‐
92               tors.  If JOBVS = 'N', VS is not referenced.
93
94       LDVS    (input) INTEGER
95               The leading dimension of the array VS.  LDVS >= 1, and if JOBVS
96               = 'V', LDVS >= N.
97
98       RCONDE  (output) DOUBLE PRECISION
99               If SENSE = 'E' or 'B', RCONDE contains the reciprocal condition
100               number for the average of the selected eigenvalues.  Not refer‐
101               enced if SENSE = 'N' or 'V'.
102
103       RCONDV  (output) DOUBLE PRECISION
104               If SENSE = 'V' or 'B', RCONDV contains the reciprocal condition
105               number  for  the selected right invariant subspace.  Not refer‐
106               enced if SENSE = 'N' or 'E'.
107
108       WORK    (workspace/output) COMPLEX*16 array, dimension (MAX(1,LWORK))
109               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
110
111       LWORK   (input) INTEGER
112               The dimension of the array WORK.  LWORK >=  max(1,2*N).   Also,
113               if  SENSE  = 'E' or 'V' or 'B', LWORK >= 2*SDIM*(N-SDIM), where
114               SDIM is the number of selected  eigenvalues  computed  by  this
115               routine.  Note that 2*SDIM*(N-SDIM) <= N*N/2. Note also that an
116               error is only returned if LWORK < max(1,2*N), but  if  SENSE  =
117               'E'  or 'V' or 'B' this may not be large enough.  For good per‐
118               formance, LWORK must generally be larger.  If LWORK = -1,  then
119               a workspace query is assumed; the routine only calculates upper
120               bound on the optimal size of the array WORK, returns this value
121               as  the  first  entry  of  the WORK array, and no error message
122               related to LWORK is issued by XERBLA.
123
124       RWORK   (workspace) DOUBLE PRECISION array, dimension (N)
125
126       BWORK   (workspace) LOGICAL array, dimension (N)
127               Not referenced if SORT = 'N'.
128
129       INFO    (output) INTEGER
130               = 0: successful exit
131               < 0: if INFO = -i, the i-th argument had an illegal value.
132               > 0: if INFO = i, and i is
133               <= N: the QR algorithm failed to compute all the
134               eigenvalues; elements 1:ILO-1 and i+1:N of W contain those  ei‐
135               genvalues which have converged; if JOBVS = 'V', VS contains the
136               transformation which reduces A to its partially converged Schur
137               form.   =  N+1:  the eigenvalues could not be reordered because
138               some eigenvalues were too close to  separate  (the  problem  is
139               very   ill-conditioned);  =  N+2:  after  reordering,  roundoff
140               changed values of some complex eigenvalues so that leading  ei‐
141               genvalues  in  the  Schur  form no longer satisfy SELECT=.TRUE.
142               This could also be caused by underflow due to scaling.
143
144
145
146 LAPACK driver routine (version 3.N2o)vember 2008                       ZGEESX(1)
Impressum