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

NAME

6       SGEES  -  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 SGEES( JOBVS,  SORT,  SELECT,  N,  A, LDA, SDIM, WR, WI, VS,
12                         LDVS, WORK, LWORK, BWORK, INFO )
13
14           CHARACTER     JOBVS, SORT
15
16           INTEGER       INFO, LDA, LDVS, LWORK, N, SDIM
17
18           LOGICAL       BWORK( * )
19
20           REAL          A( LDA, * ), VS( LDVS, * ), WI( * ), WORK( * ), WR( *
21                         )
22
23           LOGICAL       SELECT
24
25           EXTERNAL      SELECT
26

PURPOSE

28       SGEES  computes for an N-by-N real nonsymmetric matrix A, the eigenval‐
29       ues, the real Schur form T, and, optionally, the matrix of  Schur  vec‐
30       tors  Z.   This  gives the Schur factorization A = Z*T*(Z**T).  Option‐
31       ally, it also orders the eigenvalues on the diagonal of the real  Schur
32       form  so  that  selected  eigenvalues are at the top left.  The leading
33       columns of Z then form an orthonormal basis for the invariant  subspace
34       corresponding  to  the selected eigenvalues.  A matrix is in real Schur
35       form if it is upper quasi-triangular with  1-by-1  and  2-by-2  blocks.
36       2-by-2 blocks will be standardized in the form
37               [  a  b  ]
38               [  c  a  ]
39       where b*c < 0. The eigenvalues of such a block are a +- sqrt(bc).
40

ARGUMENTS

42       JOBVS   (input) CHARACTER*1
43               = 'N': Schur vectors are not computed;
44               = 'V': Schur vectors are computed.
45
46       SORT    (input) CHARACTER*1
47               Specifies whether or not to order the eigenvalues on the diago‐
48               nal of the Schur form.  = 'N': Eigenvalues are not ordered;
49               = 'S': Eigenvalues are ordered (see SELECT).
50
51       SELECT  (external procedure) LOGICAL FUNCTION of two REAL arguments
52               SELECT must be declared EXTERNAL in the calling subroutine.  If
53               SORT = 'S', SELECT is used to select eigenvalues to sort to the
54               top left of the Schur form.  If SORT = 'N', SELECT is not  ref‐
55               erenced.   An  eigenvalue  WR(j)+sqrt(-1)*WI(j)  is selected if
56               SELECT(WR(j),WI(j)) is true; i.e., if either one of  a  complex
57               conjugate  pair  of  eigenvalues is selected, then both complex
58               eigenvalues are selected.  Note that a selected complex  eigen‐
59               value  may no longer satisfy SELECT(WR(j),WI(j)) = .TRUE. after
60               ordering, since ordering may change the value of complex eigen‐
61               values  (especially  if  the eigenvalue is ill-conditioned); in
62               this case INFO is set to N+2 (see INFO below).
63
64       N       (input) INTEGER
65               The order of the matrix A. N >= 0.
66
67       A       (input/output) REAL array, dimension (LDA,N)
68               On entry, the N-by-N matrix A.  On exit, A has been overwritten
69               by its real Schur form T.
70
71       LDA     (input) INTEGER
72               The leading dimension of the array A.  LDA >= max(1,N).
73
74       SDIM    (output) INTEGER
75               If  SORT  = 'N', SDIM = 0.  If SORT = 'S', SDIM = number of ei‐
76               genvalues (after sorting) for which SELECT  is  true.  (Complex
77               conjugate  pairs for which SELECT is true for either eigenvalue
78               count as 2.)
79
80       WR      (output) REAL array, dimension (N)
81               WI      (output) REAL array, dimension (N) WR  and  WI  contain
82               the real and imaginary parts, respectively, of the computed ei‐
83               genvalues in the same order that they appear on the diagonal of
84               the  output Schur form T.  Complex conjugate pairs of eigenval‐
85               ues will appear consecutively with the  eigenvalue  having  the
86               positive imaginary part first.
87
88       VS      (output) REAL array, dimension (LDVS,N)
89               If  JOBVS  =  'V', VS contains the orthogonal matrix Z of Schur
90               vectors.  If JOBVS = 'N', VS is not referenced.
91
92       LDVS    (input) INTEGER
93               The leading dimension of the array VS.  LDVS >= 1; if  JOBVS  =
94               'V', LDVS >= N.
95
96       WORK    (workspace/output) REAL array, dimension (MAX(1,LWORK))
97               On exit, if INFO = 0, WORK(1) contains the optimal LWORK.
98
99       LWORK   (input) INTEGER
100               The  dimension  of  the  array WORK.  LWORK >= max(1,3*N).  For
101               good performance, LWORK must generally be larger.  If  LWORK  =
102               -1,  then a workspace query is assumed; the routine only calcu‐
103               lates the optimal size of the WORK array, returns this value as
104               the first entry of the WORK array, and no error message related
105               to LWORK is issued by XERBLA.
106
107       BWORK   (workspace) LOGICAL array, dimension (N)
108               Not referenced if SORT = 'N'.
109
110       INFO    (output) INTEGER
111               = 0: successful exit
112               < 0: if INFO = -i, the i-th argument had an illegal value.
113               > 0: if INFO = i, and i is
114               <= N: the QR algorithm failed to compute all the
115               eigenvalues; elements 1:ILO-1 and i+1:N of WR  and  WI  contain
116               those eigenvalues which have converged; if JOBVS = 'V', VS con‐
117               tains the matrix which reduces A  to  its  partially  converged
118               Schur  form.   =  N+1:  the  eigenvalues could not be reordered
119               because some eigenvalues were too close to separate (the  prob‐
120               lem is very ill-conditioned); = N+2: after reordering, roundoff
121               changed values of some complex eigenvalues so that leading  ei‐
122               genvalues  in  the  Schur  form no longer satisfy SELECT=.TRUE.
123               This could also be caused by underflow due to scaling.
124
125
126
127 LAPACK driver routine (version 3.N2o)vember 2008                        SGEES(1)
Impressum