1DGEEVX(1)             LAPACK driver routine (version 3.1)            DGEEVX(1)
2
3
4

NAME

6       DGEEVX - for an N-by-N real nonsymmetric matrix A, the eigenvalues and,
7       optionally, the left and/or right eigenvectors
8

SYNOPSIS

10       SUBROUTINE DGEEVX( 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           DOUBLE         PRECISION ABNRM
19
20           INTEGER        IWORK( * )
21
22           DOUBLE         PRECISION A( LDA, * ), RCONDE( *  ),  RCONDV(  *  ),
23                          SCALE(  *  ), VL( LDVL, * ), VR( LDVR, * ), WI( * ),
24                          WORK( * ), WR( * )
25

PURPOSE

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

ARGUMENTS

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