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

NAME

6       DGEESX  - 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 DGEESX( 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           DOUBLE         PRECISION RCONDE, RCONDV
20
21           LOGICAL        BWORK( * )
22
23           INTEGER        IWORK( * )
24
25           DOUBLE         PRECISION A( LDA, * ), VS( LDVS, * ), WI( * ), WORK(
26                          * ), WR( * )
27
28           LOGICAL        SELECT
29
30           EXTERNAL       SELECT
31

PURPOSE

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