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

NAME

6       CTRSNA - estimates reciprocal condition numbers for specified eigenval‐
7       ues and/or right eigenvectors of a complex upper  triangular  matrix  T
8       (or of any 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

ARGUMENTS

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

FURTHER DETAILS

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