1STREVC(1)                LAPACK routine (version 3.2)                STREVC(1)
2
3
4

NAME

6       STREVC  - computes some or all of the right and/or left eigenvectors of
7       a real upper quasi-triangular matrix T
8

SYNOPSIS

10       SUBROUTINE STREVC( SIDE, HOWMNY, SELECT, N, T, LDT, VL, LDVL, VR, LDVR,
11                          MM, M, WORK, INFO )
12
13           CHARACTER      HOWMNY, SIDE
14
15           INTEGER        INFO, LDT, LDVL, LDVR, M, MM, N
16
17           LOGICAL        SELECT( * )
18
19           REAL           T( LDT, * ), VL( LDVL, * ), VR( LDVR, * ), WORK( * )
20

PURPOSE

22       STREVC  computes some or all of the right and/or left eigenvectors of a
23       real upper quasi-triangular matrix T.  Matrices of this type  are  pro‐
24       duced  by  the  Schur  factorization  of  a  real  general matrix:  A =
25       Q*T*Q**T, as computed by SHSEQR.
26       The right eigenvector x and the left eigenvector y of  T  corresponding
27       to an eigenvalue w are defined by:
28          T*x = w*x,     (y**H)*T = w*(y**H)
29       where y**H denotes the conjugate transpose of y.
30       The  eigenvalues  are  not input to this routine, but are read directly
31       from the diagonal blocks of T.
32       This routine returns the matrices X and/or Y of right and  left  eigen‐
33       vectors  of  T,  or  the  products  Q*X and/or Q*Y, where Q is an input
34       matrix.  If Q is the orthogonal factor that reduces a matrix A to Schur
35       form  T,  then Q*X and Q*Y are the matrices of right and left eigenvec‐
36       tors of A.
37

ARGUMENTS

39       SIDE    (input) CHARACTER*1
40               = 'R':  compute right eigenvectors only;
41               = 'L':  compute left eigenvectors only;
42               = 'B':  compute both right and left eigenvectors.
43
44       HOWMNY  (input) CHARACTER*1
45               = 'A':  compute all right and/or left eigenvectors;
46               = 'B':  compute all right and/or left eigenvectors,  backtrans‐
47               formed  by  the  matrices  in  VR  and/or  VL;  = 'S':  compute
48               selected right and/or left eigenvectors, as  indicated  by  the
49               logical array SELECT.
50
51       SELECT  (input/output) LOGICAL array, dimension (N)
52               If  HOWMNY  = 'S', SELECT specifies the eigenvectors to be com‐
53               puted.  If w(j) is a real eigenvalue,  the  corresponding  real
54               eigenvector  is  computed  if SELECT(j) is .TRUE..  If w(j) and
55               w(j+1) are the real and imaginary parts of a complex  eigenval‐
56               ue, the corresponding complex eigenvector is computed if either
57               SELECT(j) or SELECT(j+1) is .TRUE., and on  exit  SELECT(j)  is
58               set  to  .TRUE.  and SELECT(j+1) is set to .FALSE..  Not refer‐
59               enced if HOWMNY = 'A' or 'B'.
60
61       N       (input) INTEGER
62               The order of the matrix T. N >= 0.
63
64       T       (input) REAL array, dimension (LDT,N)
65               The upper quasi-triangular matrix T in Schur canonical form.
66
67       LDT     (input) INTEGER
68               The leading dimension of the array T. LDT >= max(1,N).
69
70       VL      (input/output) REAL array, dimension (LDVL,MM)
71               On entry, if SIDE = 'L' or 'B' and HOWMNY = 'B', VL  must  con‐
72               tain  an  N-by-N  matrix  Q (usually the orthogonal matrix Q of
73               Schur vectors returned by SHSEQR).  On exit, if SIDE =  'L'  or
74               'B',  VL contains: if HOWMNY = 'A', the matrix Y of left eigen‐
75               vectors of T; if HOWMNY = 'B', the matrix Q*Y; if HOWMNY = 'S',
76               the left eigenvectors of T specified by SELECT, stored consecu‐
77               tively in the columns of VL, in the same order as their  eigen‐
78               values.   A  complex eigenvector corresponding to a complex ei‐
79               genvalue is stored in two consecutive columns, the first  hold‐
80               ing the real part, and the second the imaginary part.  Not ref‐
81               erenced if SIDE = 'R'.
82
83       LDVL    (input) INTEGER
84               The leading dimension of the array VL.  LDVL >= 1, and if  SIDE
85               = 'L' or 'B', LDVL >= N.
86
87       VR      (input/output) REAL array, dimension (LDVR,MM)
88               On  entry,  if SIDE = 'R' or 'B' and HOWMNY = 'B', VR must con‐
89               tain an N-by-N matrix Q (usually the  orthogonal  matrix  Q  of
90               Schur  vectors  returned by SHSEQR).  On exit, if SIDE = 'R' or
91               'B', VR contains: if HOWMNY = 'A', the matrix X of right eigen‐
92               vectors of T; if HOWMNY = 'B', the matrix Q*X; if HOWMNY = 'S',
93               the right eigenvectors of T specified by SELECT, stored consec‐
94               utively in the columns of VR, in the same order as their eigen‐
95               values.  A complex eigenvector corresponding to a  complex  ei‐
96               genvalue  is stored in two consecutive columns, the first hold‐
97               ing the real part and the second the imaginary part.  Not  ref‐
98               erenced if SIDE = 'L'.
99
100       LDVR    (input) INTEGER
101               The  leading dimension of the array VR.  LDVR >= 1, and if SIDE
102               = 'R' or 'B', LDVR >= N.
103
104       MM      (input) INTEGER
105               The number of columns in the arrays VL and/or VR. MM >= M.
106
107       M       (output) INTEGER
108               The number of columns in the arrays VL and/or VR actually  used
109               to store the eigenvectors.  If HOWMNY = 'A' or 'B', M is set to
110               N.  Each selected real eigenvector occupies one column and each
111               selected complex eigenvector occupies two columns.
112
113       WORK    (workspace) REAL array, dimension (3*N)
114
115       INFO    (output) INTEGER
116               = 0:  successful exit
117               < 0:  if INFO = -i, the i-th argument had an illegal value
118

FURTHER DETAILS

120       The algorithm used in this program is basically backward (forward) sub‐
121       stitution, with scaling to make the the code  robust  against  possible
122       overflow.
123       Each eigenvector is normalized so that the element of largest magnitude
124       has magnitude 1; here the magnitude of a complex number (x,y) is  taken
125       to be |x| + |y|.
126
127
128
129 LAPACK routine (version 3.2)    November 2008                       STREVC(1)
Impressum