1DTRSNA(1)                LAPACK routine (version 3.1)                DTRSNA(1)
2
3
4

NAME

6       DTRSNA  - reciprocal condition numbers for specified eigenvalues and/or
7       right eigenvectors of a real upper quasi-triangular matrix T (or of any
8       matrix Q*T*Q**T with Q orthogonal)
9

SYNOPSIS

11       SUBROUTINE DTRSNA( JOB,  HOWMNY, SELECT, N, T, LDT, VL, LDVL, VR, LDVR,
12                          S, SEP, MM, M, WORK, LDWORK, IWORK, INFO )
13
14           CHARACTER      HOWMNY, JOB
15
16           INTEGER        INFO, LDT, LDVL, LDVR, LDWORK, M, MM, N
17
18           LOGICAL        SELECT( * )
19
20           INTEGER        IWORK( * )
21
22           DOUBLE         PRECISION S( * ), SEP( * ), T( LDT, * ), VL( LDVL, *
23                          ), VR( LDVR, * ), WORK( LDWORK, * )
24

PURPOSE

26       DTRSNA estimates reciprocal condition numbers for specified eigenvalues
27       and/or right eigenvectors of a real upper quasi-triangular matrix T (or
28       of any matrix Q*T*Q**T with Q orthogonal).
29
30       T  must  be  in  Schur canonical form (as returned by DHSEQR), that is,
31       block upper triangular with 1-by-1 and  2-by-2  diagonal  blocks;  each
32       2-by-2 diagonal block has its diagonal elements equal and its off-diag‐
33       onal elements of opposite sign.
34
35

ARGUMENTS

37       JOB     (input) CHARACTER*1
38               Specifies whether condition numbers are required for  eigenval‐
39               ues (S) or eigenvectors (SEP):
40               = 'E': for eigenvalues only (S);
41               = 'V': for eigenvectors only (SEP);
42               = 'B': for both eigenvalues and eigenvectors (S and SEP).
43
44       HOWMNY  (input) CHARACTER*1
45               = 'A': compute condition numbers for all eigenpairs;
46               = 'S': compute condition numbers for selected eigenpairs speci‐
47               fied by the array SELECT.
48
49       SELECT  (input) LOGICAL array, dimension (N)
50               If HOWMNY = 'S', SELECT specifies the eigenpairs for which con‐
51               dition  numbers  are  required. To select condition numbers for
52               the  eigenpair  corresponding  to  a  real   eigenvalue   w(j),
53               SELECT(j)  must  be  set to .TRUE.. To select condition numbers
54               corresponding to a complex conjugate pair of  eigenvalues  w(j)
55               and  w(j+1),  either  SELECT(j) or SELECT(j+1) or both, must be
56               set to .TRUE..  If HOWMNY = 'A', SELECT is not referenced.
57
58       N       (input) INTEGER
59               The order of the matrix T. N >= 0.
60
61       T       (input) DOUBLE PRECISION array, dimension (LDT,N)
62               The upper quasi-triangular matrix T, in Schur canonical form.
63
64       LDT     (input) INTEGER
65               The leading dimension of the array T. LDT >= max(1,N).
66
67       VL      (input) DOUBLE PRECISION array, dimension (LDVL,M)
68               If JOB = 'E' or 'B', VL must contain left eigenvectors of T (or
69               of any Q*T*Q**T with Q orthogonal), corresponding to the eigen‐
70               pairs specified by HOWMNY and SELECT. The eigenvectors must  be
71               stored  in  consecutive columns of VL, as returned by DHSEIN or
72               DTREVC.  If JOB = 'V', VL is not referenced.
73
74       LDVL    (input) INTEGER
75               The leading dimension of the array VL.  LDVL >= 1; and if JOB =
76               'E' or 'B', LDVL >= N.
77
78       VR      (input) DOUBLE PRECISION array, dimension (LDVR,M)
79               If  JOB  =  'E' or 'B', VR must contain right eigenvectors of T
80               (or of any Q*T*Q**T with Q orthogonal),  corresponding  to  the
81               eigenpairs  specified  by  HOWMNY  and SELECT. The eigenvectors
82               must be stored in consecutive columns of  VR,  as  returned  by
83               DHSEIN or DTREVC.  If JOB = 'V', VR is not referenced.
84
85       LDVR    (input) INTEGER
86               The leading dimension of the array VR.  LDVR >= 1; and if JOB =
87               'E' or 'B', LDVR >= N.
88
89       S       (output) DOUBLE PRECISION array, dimension (MM)
90               If JOB = 'E' or 'B', the reciprocal condition  numbers  of  the
91               selected  eigenvalues,  stored  in  consecutive elements of the
92               array. For a complex conjugate pair of eigenvalues two consecu‐
93               tive  elements  of  S  are  set  to  the same value. Thus S(j),
94               SEP(j), and the j-th columns of VL and VR all correspond to the
95               same  eigenpair  (but not in general the j-th eigenpair, unless
96               all eigenpairs are selected).  If JOB = 'V', S  is  not  refer‐
97               enced.
98
99       SEP     (output) DOUBLE PRECISION array, dimension (MM)
100               If JOB = 'V' or 'B', the estimated reciprocal condition numbers
101               of the selected eigenvectors, stored in consecutive elements of
102               the  array.  For a complex eigenvector two consecutive elements
103               of SEP are set to the same value. If the eigenvalues cannot  be
104               reordered  to compute SEP(j), SEP(j) is set to 0; this can only
105               occur when the true value would be very small anyway.  If JOB =
106               'E', SEP is not referenced.
107
108       MM      (input) INTEGER
109               The  number  of  elements in the arrays S (if JOB = 'E' or 'B')
110               and/or SEP (if JOB = 'V' or 'B'). MM >= M.
111
112       M       (output) INTEGER
113               The number of elements of the arrays S and/or SEP actually used
114               to  store  the estimated condition numbers.  If HOWMNY = 'A', M
115               is set to N.
116
117       WORK    (workspace) DOUBLE PRECISION array, dimension (LDWORK,N+6)
118               If JOB = 'E', WORK is not referenced.
119
120       LDWORK  (input) INTEGER
121               The leading dimension of the array WORK.  LDWORK >= 1;  and  if
122               JOB = 'V' or 'B', LDWORK >= N.
123
124       IWORK   (workspace) INTEGER array, dimension (2*(N-1))
125               If JOB = 'E', IWORK is not referenced.
126
127       INFO    (output) INTEGER
128               = 0: successful exit
129               < 0: if INFO = -i, the i-th argument had an illegal value
130

FURTHER DETAILS

132       The  reciprocal  of  the  condition  number  of an eigenvalue lambda is
133       defined as
134
135               S(lambda) = |v'*u| / (norm(u)*norm(v))
136
137       where u and v are the right and left eigenvectors of T corresponding to
138       lambda;  v'  denotes  the conjugate-transpose of v, and norm(u) denotes
139       the Euclidean norm.  These  reciprocal  condition  numbers  always  lie
140       between  zero (very badly conditioned) and one (very well conditioned).
141       If n = 1, S(lambda) is defined to be 1.
142
143       An approximate error bound for a computed eigenvalue W(i) is given by
144
145                           EPS * norm(T) / S(i)
146
147       where EPS is the machine precision.
148
149       The reciprocal of the condition number of the right eigenvector u  cor‐
150       responding to lambda is defined as follows. Suppose
151
152                   T = ( lambda  c  )
153                       (   0    T22 )
154
155       Then the reciprocal condition number is
156
157               SEP( lambda, T22 ) = sigma-min( T22 - lambda*I )
158
159       where sigma-min denotes the smallest singular value. We approximate the
160       smallest singular value by the reciprocal of an estimate  of  the  one-
161       norm  of  the inverse of T22 - lambda*I. If n = 1, SEP(1) is defined to
162       be abs(T(1,1)).
163
164       An approximate error bound for a computed right  eigenvector  VR(i)  is
165       given by
166
167                           EPS * norm(T) / SEP(i)
168
169
170
171
172 LAPACK routine (version 3.1)    November 2006                       DTRSNA(1)
Impressum