1SLAR1V(1) LAPACK auxiliary routine (version 3.1) SLAR1V(1)
2
3
4
6 SLAR1V - the (scaled) r-th column of the inverse of the sumbmatrix in
7 rows B1 through BN of the tridiagonal matrix L D L^T - sigma I
8
10 SUBROUTINE SLAR1V( N, B1, BN, LAMBDA, D, L, LD, LLD, PIVMIN, GAPTOL, Z,
11 WANTNC, NEGCNT, ZTZ, MINGMA, R, ISUPPZ, NRMINV,
12 RESID, RQCORR, WORK )
13
14 LOGICAL WANTNC
15
16 INTEGER B1, BN, N, NEGCNT, R
17
18 REAL GAPTOL, LAMBDA, MINGMA, NRMINV, PIVMIN, RESID,
19 RQCORR, ZTZ
20
21 INTEGER ISUPPZ( * )
22
23 REAL D( * ), L( * ), LD( * ), LLD( * ), WORK( * )
24
25 REAL Z( * )
26
28 SLAR1V computes the (scaled) r-th column of the inverse of the sumbma‐
29 trix in rows B1 through BN of the tridiagonal matrix L D L^T - sigma I.
30 When sigma is close to an eigenvalue, the computed vector is an accu‐
31 rate eigenvector. Usually, r corresponds to the index where the eigen‐
32 vector is largest in magnitude. The following steps accomplish this
33 computation :
34 (a) Stationary qd transform, L D L^T - sigma I = L(+) D(+) L(+)^T, (b)
35 Progressive qd transform, L D L^T - sigma I = U(-) D(-) U(-)^T, (c)
36 Computation of the diagonal elements of the inverse of
37 L D L^T - sigma I by combining the above transforms, and choosing
38 r as the index where the diagonal of the inverse is (one of the)
39 largest in magnitude.
40 (d) Computation of the (scaled) r-th column of the inverse using the
41 twisted factorization obtained by combining the top part of the
42 the stationary and the bottom part of the progressive transform.
43
44
46 N (input) INTEGER
47 The order of the matrix L D L^T.
48
49 B1 (input) INTEGER
50 First index of the submatrix of L D L^T.
51
52 BN (input) INTEGER
53 Last index of the submatrix of L D L^T.
54
55 LAMBDA (input) REAL
56 The shift. In order to compute an accurate eigenvector,
57 LAMBDA should be a good approximation to an eigenvalue of L D
58 L^T.
59
60 L (input) REAL array, dimension (N-1)
61 The (n-1) subdiagonal elements of the unit bidiagonal matrix
62 L, in elements 1 to N-1.
63
64 D (input) REAL array, dimension (N)
65 The n diagonal elements of the diagonal matrix D.
66
67 LD (input) REAL array, dimension (N-1)
68 The n-1 elements L(i)*D(i).
69
70 LLD (input) REAL array, dimension (N-1)
71 The n-1 elements L(i)*L(i)*D(i).
72
73 PIVMIN (input) REAL
74 The minimum pivot in the Sturm sequence.
75
76 GAPTOL (input) REAL
77 Tolerance that indicates when eigenvector entries are negligi‐
78 ble w.r.t. their contribution to the residual.
79
80 Z (input/output) REAL array, dimension (N)
81 On input, all entries of Z must be set to 0. On output, Z
82 contains the (scaled) r-th column of the inverse. The scaling
83 is such that Z(R) equals 1.
84
85 WANTNC (input) LOGICAL
86 Specifies whether NEGCNT has to be computed.
87
88 NEGCNT (output) INTEGER
89 If WANTNC is .TRUE. then NEGCNT = the number of pivots <
90 pivmin in the matrix factorization L D L^T, and NEGCNT = -1
91 otherwise.
92
93 ZTZ (output) REAL
94 The square of the 2-norm of Z.
95
96 MINGMA (output) REAL
97 The reciprocal of the largest (in magnitude) diagonal element
98 of the inverse of L D L^T - sigma I.
99
100 R (input/output) INTEGER
101 The twist index for the twisted factorization used to compute
102 Z. On input, 0 <= R <= N. If R is input as 0, R is set to the
103 index where (L D L^T - sigma I)^{-1} is largest in magnitude.
104 If 1 <= R <= N, R is unchanged. On output, R contains the
105 twist index used to compute Z. Ideally, R designates the
106 position of the maximum entry in the eigenvector.
107
108 ISUPPZ (output) INTEGER array, dimension (2)
109 The support of the vector in Z, i.e., the vector Z is nonzero
110 only in elements ISUPPZ(1) through ISUPPZ( 2 ).
111
112 NRMINV (output) REAL
113 NRMINV = 1/SQRT( ZTZ )
114
115 RESID (output) REAL
116 The residual of the FP vector. RESID = ABS( MINGMA )/SQRT(
117 ZTZ )
118
119 RQCORR (output) REAL
120 The Rayleigh Quotient correction to LAMBDA. RQCORR =
121 MINGMA*TMP
122
123 WORK (workspace) REAL array, dimension (4*N)
124
126 Based on contributions by
127 Beresford Parlett, University of California, Berkeley, USA
128 Jim Demmel, University of California, Berkeley, USA
129 Inderjit Dhillon, University of Texas, Austin, USA
130 Osni Marques, LBNL/NERSC, USA
131 Christof Voemel, University of California, Berkeley, USA
132
133
134
135
136 LAPACK auxiliary routine (versionNo3v.e1m)ber 2006 SLAR1V(1)