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

NAME

6       CTRSNA  - reciprocal condition numbers for specified eigenvalues and/or
7       right eigenvectors of a complex upper triangular matrix T  (or  of  any
8       matrix Q*T*Q**H with Q unitary)
9

SYNOPSIS

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

PURPOSE

26       CTRSNA estimates reciprocal condition numbers for specified eigenvalues
27       and/or right eigenvectors of a complex upper triangular matrix T (or of
28       any matrix Q*T*Q**H with Q unitary).
29
30

ARGUMENTS

32       JOB     (input) CHARACTER*1
33               Specifies  whether condition numbers are required for eigenval‐
34               ues (S) or eigenvectors (SEP):
35               = 'E': for eigenvalues only (S);
36               = 'V': for eigenvectors only (SEP);
37               = 'B': for both eigenvalues and eigenvectors (S and SEP).
38
39       HOWMNY  (input) CHARACTER*1
40               = 'A': compute condition numbers for all eigenpairs;
41               = 'S': compute condition numbers for selected eigenpairs speci‐
42               fied by the array SELECT.
43
44       SELECT  (input) LOGICAL array, dimension (N)
45               If HOWMNY = 'S', SELECT specifies the eigenpairs for which con‐
46               dition numbers are required. To select  condition  numbers  for
47               the j-th eigenpair, SELECT(j) must be set to .TRUE..  If HOWMNY
48               = 'A', SELECT is not referenced.
49
50       N       (input) INTEGER
51               The order of the matrix T. N >= 0.
52
53       T       (input) COMPLEX array, dimension (LDT,N)
54               The upper triangular matrix T.
55
56       LDT     (input) INTEGER
57               The leading dimension of the array T. LDT >= max(1,N).
58
59       VL      (input) COMPLEX array, dimension (LDVL,M)
60               If JOB = 'E' or 'B', VL must contain left eigenvectors of T (or
61               of  any  Q*T*Q**H  with Q unitary), corresponding to the eigen‐
62               pairs specified by HOWMNY and SELECT. The eigenvectors must  be
63               stored  in  consecutive columns of VL, as returned by CHSEIN or
64               CTREVC.  If JOB = 'V', VL is not referenced.
65
66       LDVL    (input) INTEGER
67               The leading dimension of the array VL.  LDVL >= 1; and if JOB =
68               'E' or 'B', LDVL >= N.
69
70       VR      (input) COMPLEX array, dimension (LDVR,M)
71               If  JOB  =  'E' or 'B', VR must contain right eigenvectors of T
72               (or of any Q*T*Q**H  with  Q  unitary),  corresponding  to  the
73               eigenpairs  specified  by  HOWMNY  and SELECT. The eigenvectors
74               must be stored in consecutive columns of  VR,  as  returned  by
75               CHSEIN or CTREVC.  If JOB = 'V', VR is not referenced.
76
77       LDVR    (input) INTEGER
78               The leading dimension of the array VR.  LDVR >= 1; and if JOB =
79               'E' or 'B', LDVR >= N.
80
81       S       (output) REAL array, dimension (MM)
82               If JOB = 'E' or 'B', the reciprocal condition  numbers  of  the
83               selected  eigenvalues,  stored  in  consecutive elements of the
84               array. Thus S(j), SEP(j), and the j-th columns of VL and VR all
85               correspond  to  the same eigenpair (but not in general the j-th
86               eigenpair, unless all eigenpairs are selected).  If JOB =  'V',
87               S is not referenced.
88
89       SEP     (output) REAL array, dimension (MM)
90               If JOB = 'V' or 'B', the estimated reciprocal condition numbers
91               of the selected eigenvectors, stored in consecutive elements of
92               the array.  If JOB = 'E', SEP is not referenced.
93
94       MM      (input) INTEGER
95               The  number  of  elements in the arrays S (if JOB = 'E' or 'B')
96               and/or SEP (if JOB = 'V' or 'B'). MM >= M.
97
98       M       (output) INTEGER
99               The number of elements of the arrays S and/or SEP actually used
100               to  store  the estimated condition numbers.  If HOWMNY = 'A', M
101               is set to N.
102
103       WORK    (workspace) COMPLEX array, dimension (LDWORK,N+6)
104               If JOB = 'E', WORK is not referenced.
105
106       LDWORK  (input) INTEGER
107               The leading dimension of the array WORK.  LDWORK >= 1;  and  if
108               JOB = 'V' or 'B', LDWORK >= N.
109
110       RWORK   (workspace) REAL array, dimension (N)
111               If JOB = 'E', RWORK is not referenced.
112
113       INFO    (output) INTEGER
114               = 0: successful exit
115               < 0: if INFO = -i, the i-th argument had an illegal value
116

FURTHER DETAILS

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