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