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

NAME

6       SGEESX  - computes for an N-by-N real nonsymmetric matrix A, the eigen‐
7       values, the real Schur form T, and, optionally,  the  matrix  of  Schur
8       vectors Z
9

SYNOPSIS

11       SUBROUTINE SGEESX( JOBVS, SORT, SELECT, SENSE, N, A, LDA, SDIM, WR, WI,
12                          VS,  LDVS,  RCONDE,  RCONDV,  WORK,  LWORK,   IWORK,
13                          LIWORK, BWORK, INFO )
14
15           CHARACTER      JOBVS, SENSE, SORT
16
17           INTEGER        INFO, LDA, LDVS, LIWORK, LWORK, N, SDIM
18
19           REAL           RCONDE, RCONDV
20
21           LOGICAL        BWORK( * )
22
23           INTEGER        IWORK( * )
24
25           REAL           A(  LDA, * ), VS( LDVS, * ), WI( * ), WORK( * ), WR(
26                          * )
27
28           LOGICAL        SELECT
29
30           EXTERNAL       SELECT
31

PURPOSE

33       SGEESX computes for an N-by-N real nonsymmetric matrix A, the eigenval‐
34       ues,  the  real Schur form T, and, optionally, the matrix of Schur vec‐
35       tors Z.  This gives the Schur factorization A  =  Z*T*(Z**T).   Option‐
36       ally,  it also orders the eigenvalues on the diagonal of the real Schur
37       form so that selected eigenvalues are  at  the  top  left;  computes  a
38       reciprocal condition number for the average of the selected eigenvalues
39       (RCONDE); and computes a reciprocal  condition  number  for  the  right
40       invariant  subspace corresponding to the selected eigenvalues (RCONDV).
41       The leading columns of Z form an orthonormal basis for  this  invariant
42       subspace.
43       For  further explanation of the reciprocal condition numbers RCONDE and
44       RCONDV, see Section 4.10 of the LAPACK Users' Guide (where these  quan‐
45       tities are called s and sep respectively).
46       A  real  matrix  is  in real Schur form if it is upper quasi-triangular
47       with 1-by-1 and 2-by-2 blocks. 2-by-2 blocks will  be  standardized  in
48       the form
49                 [  a  b  ]
50                 [  c  a  ]
51       where b*c < 0. The eigenvalues of such a block are a +- sqrt(bc).
52

ARGUMENTS

54       JOBVS   (input) CHARACTER*1
55               = 'N': Schur vectors are not computed;
56               = 'V': Schur vectors are computed.
57
58       SORT    (input) CHARACTER*1
59               Specifies whether or not to order the eigenvalues on the diago‐
60               nal of the Schur form.  = 'N': Eigenvalues are not ordered;
61               = 'S': Eigenvalues are ordered (see SELECT).
62
63       SELECT  (external procedure) LOGICAL FUNCTION of two REAL arguments
64               SELECT must be declared EXTERNAL in the calling subroutine.  If
65               SORT = 'S', SELECT is used to select eigenvalues to sort to the
66               top left of the Schur form.  If SORT = 'N', SELECT is not  ref‐
67               erenced.   An  eigenvalue  WR(j)+sqrt(-1)*WI(j)  is selected if
68               SELECT(WR(j),WI(j)) is true; i.e., if either one of  a  complex
69               conjugate pair of eigenvalues is selected, then both are.  Note
70               that a  selected  complex  eigenvalue  may  no  longer  satisfy
71               SELECT(WR(j),WI(j)) = .TRUE. after ordering, since ordering may
72               change the value of complex eigenvalues (especially if the  ei‐
73               genvalue  is  ill-conditioned); in this case INFO may be set to
74               N+3 (see INFO below).
75
76       SENSE   (input) CHARACTER*1
77               Determines which reciprocal condition numbers are computed.   =
78               'N': None are computed;
79               = 'E': Computed for average of selected eigenvalues only;
80               = 'V': Computed for selected right invariant subspace only;
81               =  'B':  Computed  for  both.  If SENSE = 'E', 'V' or 'B', SORT
82               must equal 'S'.
83
84       N       (input) INTEGER
85               The order of the matrix A. N >= 0.
86
87       A       (input/output) REAL array, dimension (LDA, N)
88               On entry, the N-by-N matrix A.  On exit, A  is  overwritten  by
89               its real Schur form T.
90
91       LDA     (input) INTEGER
92               The leading dimension of the array A.  LDA >= max(1,N).
93
94       SDIM    (output) INTEGER
95               If  SORT  = 'N', SDIM = 0.  If SORT = 'S', SDIM = number of ei‐
96               genvalues (after sorting) for which SELECT  is  true.  (Complex
97               conjugate  pairs for which SELECT is true for either eigenvalue
98               count as 2.)
99
100       WR      (output) REAL array, dimension (N)
101               WI      (output) REAL array, dimension (N) WR  and  WI  contain
102               the real and imaginary parts, respectively, of the computed ei‐
103               genvalues, in the same order that they appear on  the  diagonal
104               of  the output Schur form T.  Complex conjugate pairs of eigen‐
105               values appear consecutively with the eigenvalue having the pos‐
106               itive imaginary part first.
107
108       VS      (output) REAL array, dimension (LDVS,N)
109               If  JOBVS  =  'V', VS contains the orthogonal matrix Z of Schur
110               vectors.  If JOBVS = 'N', VS is not referenced.
111
112       LDVS    (input) INTEGER
113               The leading dimension of the array VS.  LDVS >= 1, and if JOBVS
114               = 'V', LDVS >= N.
115
116       RCONDE  (output) REAL
117               If SENSE = 'E' or 'B', RCONDE contains the reciprocal condition
118               number for the average of the selected eigenvalues.  Not refer‐
119               enced if SENSE = 'N' or 'V'.
120
121       RCONDV  (output) REAL
122               If SENSE = 'V' or 'B', RCONDV contains the reciprocal condition
123               number for the selected right invariant subspace.   Not  refer‐
124               enced if SENSE = 'N' or 'E'.
125
126       WORK    (workspace/output) REAL array, dimension (MAX(1,LWORK))
127               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
128
129       LWORK   (input) INTEGER
130               The  dimension  of the array WORK.  LWORK >= max(1,3*N).  Also,
131               if SENSE = 'E' or 'V' or 'B', LWORK >= N+2*SDIM*(N-SDIM), where
132               SDIM  is  the  number  of selected eigenvalues computed by this
133               routine.  Note that N+2*SDIM*(N-SDIM)  <=  N+N*N/2.  Note  also
134               that  an  error  is only returned if LWORK < max(1,3*N), but if
135               SENSE = 'E' or 'V' or 'B' this may not be  large  enough.   For
136               good  performance,  LWORK must generally be larger.  If LWORK =
137               -1, then a workspace query is assumed; the routine only  calcu‐
138               lates  upper bounds on the optimal sizes of the arrays WORK and
139               IWORK, returns these values as the first entries  of  the  WORK
140               and  IWORK  arrays,  and  no error messages related to LWORK or
141               LIWORK are issued by XERBLA.
142
143       IWORK   (workspace/output) INTEGER array, dimension (MAX(1,LIWORK))
144               On exit, if INFO = 0, IWORK(1) returns the optimal LIWORK.
145
146       LIWORK  (input) INTEGER
147               The dimension of the array IWORK.  LIWORK >= 1; if SENSE =  'V'
148               or  'B',  LIWORK  >= SDIM*(N-SDIM).  Note that SDIM*(N-SDIM) <=
149               N*N/4. Note also that an error is only returned if LIWORK <  1,
150               but  if  SENSE  =  'V' or 'B' this may not be large enough.  If
151               LIWORK = -1, then a workspace query  is  assumed;  the  routine
152               only calculates upper bounds on the optimal sizes of the arrays
153               WORK and IWORK, returns these values as the  first  entries  of
154               the  WORK  and  IWORK  arrays, and no error messages related to
155               LWORK or LIWORK are issued by XERBLA.
156
157       BWORK   (workspace) LOGICAL array, dimension (N)
158               Not referenced if SORT = 'N'.
159
160       INFO    (output) INTEGER
161               = 0: successful exit
162               < 0: if INFO = -i, the i-th argument had an illegal value.
163               > 0: if INFO = i, and i is
164               <= N: the QR algorithm failed to compute all the
165               eigenvalues; elements 1:ILO-1 and i+1:N of WR  and  WI  contain
166               those eigenvalues which have converged; if JOBVS = 'V', VS con‐
167               tains the transformation which reduces A to its partially  con‐
168               verged  Schur  form.   =  N+1:  the  eigenvalues  could  not be
169               reordered because some eigenvalues were too close  to  separate
170               (the problem is very ill-conditioned); = N+2: after reordering,
171               roundoff changed values of some  complex  eigenvalues  so  that
172               leading  eigenvalues  in  the  Schur  form  no  longer  satisfy
173               SELECT=.TRUE.  This could also be caused by  underflow  due  to
174               scaling.
175
176
177
178 LAPACK driver routine (version 3.N2o)vember 2008                       SGEESX(1)
Impressum