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

NAME

6       SGEEVX  - computes for an N-by-N real nonsymmetric matrix A, the eigen‐
7       values and, optionally, the left and/or right eigenvectors
8

SYNOPSIS

10       SUBROUTINE SGEEVX( BALANC, JOBVL, JOBVR, SENSE, N, A, LDA, WR, WI,  VL,
11                          LDVL,  VR,  LDVR,  ILO,  IHI,  SCALE, ABNRM, RCONDE,
12                          RCONDV, WORK, LWORK, IWORK, INFO )
13
14           CHARACTER      BALANC, JOBVL, JOBVR, SENSE
15
16           INTEGER        IHI, ILO, INFO, LDA, LDVL, LDVR, LWORK, N
17
18           REAL           ABNRM
19
20           INTEGER        IWORK( * )
21
22           REAL           A( LDA, * ), RCONDE( * ), RCONDV( * ), SCALE(  *  ),
23                          VL(  LDVL,  *  ), VR( LDVR, * ), WI( * ), WORK( * ),
24                          WR( * )
25

PURPOSE

27       SGEEVX computes for an N-by-N real nonsymmetric matrix A, the eigenval‐
28       ues  and,  optionally,  the left and/or right eigenvectors.  Optionally
29       also, it computes a balancing transformation to improve the  condition‐
30       ing  of  the eigenvalues and eigenvectors (ILO, IHI, SCALE, and ABNRM),
31       reciprocal condition numbers for the eigenvalues (RCONDE), and recipro‐
32       cal condition numbers for the right
33       eigenvectors (RCONDV).
34       The right eigenvector v(j) of A satisfies
35                        A * v(j) = lambda(j) * v(j)
36       where lambda(j) is its eigenvalue.
37       The left eigenvector u(j) of A satisfies
38                     u(j)**H * A = lambda(j) * u(j)**H
39       where u(j)**H denotes the conjugate transpose of u(j).
40       The  computed  eigenvectors are normalized to have Euclidean norm equal
41       to 1 and largest component real.
42       Balancing a matrix means permuting the rows and columns to make it more
43       nearly upper triangular, and applying a diagonal similarity transforma‐
44       tion D * A * D**(-1), where D is a diagonal matrix, to  make  its  rows
45       and columns closer in norm and the condition numbers of its eigenvalues
46       and eigenvectors smaller.  The computed  reciprocal  condition  numbers
47       correspond to the balanced matrix.  Permuting rows and columns will not
48       change the condition numbers (in exact arithmetic) but diagonal scaling
49       will.   For further explanation of balancing, see section 4.10.2 of the
50       LAPACK Users' Guide.
51

ARGUMENTS

53       BALANC  (input) CHARACTER*1
54               Indicates how the input  matrix  should  be  diagonally  scaled
55               and/or permuted to improve the conditioning of its eigenvalues.
56               = 'N': Do not diagonally scale or permute;
57               = 'P': Perform permutations to  make  the  matrix  more  nearly
58               upper  triangular.  Do  not diagonally scale; = 'S': Diagonally
59               scale the matrix, i.e. replace A by D*A*D**(-1), where D  is  a
60               diagonal  matrix  chosen to make the rows and columns of A more
61               equal in norm. Do not permute; = 'B': Both diagonally scale and
62               permute  A.   Computed reciprocal condition numbers will be for
63               the matrix after balancing and/or permuting. Permuting does not
64               change  condition  numbers (in exact arithmetic), but balancing
65               does.
66
67       JOBVL   (input) CHARACTER*1
68               = 'N': left eigenvectors of A are not computed;
69               = 'V': left eigenvectors of A are computed.  If SENSE = 'E'  or
70               'B', JOBVL must = 'V'.
71
72       JOBVR   (input) CHARACTER*1
73               = 'N': right eigenvectors of A are not computed;
74               = 'V': right eigenvectors of A are computed.  If SENSE = 'E' or
75               'B', JOBVR must = 'V'.
76
77       SENSE   (input) CHARACTER*1
78               Determines which reciprocal condition numbers are computed.   =
79               'N': None are computed;
80               = 'E': Computed for eigenvalues only;
81               = 'V': Computed for right eigenvectors only;
82               =  'B':  Computed  for  eigenvalues and right eigenvectors.  If
83               SENSE = 'E' or 'B', both left and right eigenvectors must  also
84               be computed (JOBVL = 'V' and JOBVR = 'V').
85
86       N       (input) INTEGER
87               The order of the matrix A. N >= 0.
88
89       A       (input/output) REAL array, dimension (LDA,N)
90               On  entry,  the N-by-N matrix A.  On exit, A has been overwrit‐
91               ten.  If JOBVL = 'V' or JOBVR = 'V', A contains the real  Schur
92               form of the balanced version of the input matrix A.
93
94       LDA     (input) INTEGER
95               The leading dimension of the array A.  LDA >= max(1,N).
96
97       WR      (output) REAL array, dimension (N)
98               WI       (output)  REAL  array, dimension (N) WR and WI contain
99               the real and imaginary parts, respectively, of the computed ei‐
100               genvalues.   Complex conjugate pairs of eigenvalues will appear
101               consecutively with the eigenvalue having the positive imaginary
102               part first.
103
104       VL      (output) REAL array, dimension (LDVL,N)
105               If JOBVL = 'V', the left eigenvectors u(j) are stored one after
106               another in the columns of VL, in the same order as their eigen‐
107               values.  If JOBVL = 'N', VL is not referenced.  If the j-th ei‐
108               genvalue is real, then u(j) = VL(:,j), the j-th column  of  VL.
109               If  the  j-th and (j+1)-st eigenvalues form a complex conjugate
110               pair, then u(j) = VL(:,j) + i*VL(:,j+1) and
111               u(j+1) = VL(:,j) - i*VL(:,j+1).
112
113       LDVL    (input) INTEGER
114               The leading dimension of the array VL.  LDVL >= 1; if  JOBVL  =
115               'V', LDVL >= N.
116
117       VR      (output) REAL array, dimension (LDVR,N)
118               If  JOBVR  =  'V',  the  right eigenvectors v(j) are stored one
119               after another in the columns of VR, in the same order as  their
120               eigenvalues.   If JOBVR = 'N', VR is not referenced.  If the j-
121               th eigenvalue is real, then v(j) = VR(:,j), the j-th column  of
122               VR.  If the j-th and (j+1)-st eigenvalues form a complex conju‐
123               gate pair, then v(j) = VR(:,j) + i*VR(:,j+1) and
124               v(j+1) = VR(:,j) - i*VR(:,j+1).
125
126       LDVR    (input) INTEGER
127               The leading dimension of the array VR.  LDVR >= 1, and if JOBVR
128               = 'V', LDVR >= N.
129
130       ILO     (output) INTEGER
131               IHI      (output) INTEGER ILO and IHI are integer values deter‐
132               mined when A was balanced.  The balanced A(i,j) = 0 if  I  >  J
133               and J = 1,...,ILO-1 or I = IHI+1,...,N.
134
135       SCALE   (output) REAL array, dimension (N)
136               Details  of  the  permutations and scaling factors applied when
137               balancing A.  If P(j) is the index of the row and column inter‐
138               changed  with  row and column j, and D(j) is the scaling factor
139               applied to row and column j, then SCALE(J) = P(J),    for  J  =
140               1,...,ILO-1  =  D(J),    for J = ILO,...,IHI = P(J)     for J =
141               IHI+1,...,N.  The order in which the interchanges are made is N
142               to IHI+1, then 1 to ILO-1.
143
144       ABNRM   (output) REAL
145               The  one-norm of the balanced matrix (the maximum of the sum of
146               absolute values of elements of any column).
147
148       RCONDE  (output) REAL array, dimension (N)
149               RCONDE(j) is the reciprocal condition number of the j-th eigen‐
150               value.
151
152       RCONDV  (output) REAL array, dimension (N)
153               RCONDV(j)  is the reciprocal condition number of the j-th right
154               eigenvector.
155
156       WORK    (workspace/output) REAL array, dimension (MAX(1,LWORK))
157               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
158
159       LWORK   (input) INTEGER
160               The dimension of the array WORK.   If SENSE = 'N' or 'E', LWORK
161               >= max(1,2*N), and if JOBVL = 'V' or JOBVR = 'V', LWORK >= 3*N.
162               If SENSE = 'V' or 'B', LWORK >= N*(N+6).  For good performance,
163               LWORK  must  generally  be  larger.   If  LWORK  =  -1,  then a
164               workspace query is assumed; the  routine  only  calculates  the
165               optimal size of the WORK array, returns this value as the first
166               entry of the WORK array, and no error message related to  LWORK
167               is issued by XERBLA.
168
169       IWORK   (workspace) INTEGER array, dimension (2*N-2)
170               If SENSE = 'N' or 'E', not referenced.
171
172       INFO    (output) INTEGER
173               = 0:  successful exit
174               < 0:  if INFO = -i, the i-th argument had an illegal value.
175               >  0:   if INFO = i, the QR algorithm failed to compute all the
176               eigenvalues, and no eigenvectors or condition numbers have been
177               computed;  elements  1:ILO-1 and i+1:N of WR and WI contain ei‐
178               genvalues which have converged.
179
180
181
182 LAPACK driver routine (version 3.N2o)vember 2008                       SGEEVX(1)
Impressum