LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dlarrk.f
Go to the documentation of this file.
1*> \brief \b DLARRK computes one eigenvalue of a symmetric tridiagonal matrix T to suitable accuracy.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DLARRK + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlarrk.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlarrk.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlarrk.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DLARRK( N, IW, GL, GU,
20* D, E2, PIVMIN, RELTOL, W, WERR, INFO)
21*
22* .. Scalar Arguments ..
23* INTEGER INFO, IW, N
24* DOUBLE PRECISION PIVMIN, RELTOL, GL, GU, W, WERR
25* ..
26* .. Array Arguments ..
27* DOUBLE PRECISION D( * ), E2( * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> DLARRK computes one eigenvalue of a symmetric tridiagonal
37*> matrix T to suitable accuracy. This is an auxiliary code to be
38*> called from DSTEMR.
39*>
40*> To avoid overflow, the matrix must be scaled so that its
41*> largest element is no greater than overflow**(1/2) * underflow**(1/4) in absolute value, and for greatest
42*> accuracy, it should not be much smaller than that.
43*>
44*> See W. Kahan "Accurate Eigenvalues of a Symmetric Tridiagonal
45*> Matrix", Report CS41, Computer Science Dept., Stanford
46*> University, July 21, 1966.
47*> \endverbatim
48*
49* Arguments:
50* ==========
51*
52*> \param[in] N
53*> \verbatim
54*> N is INTEGER
55*> The order of the tridiagonal matrix T. N >= 0.
56*> \endverbatim
57*>
58*> \param[in] IW
59*> \verbatim
60*> IW is INTEGER
61*> The index of the eigenvalues to be returned.
62*> \endverbatim
63*>
64*> \param[in] GL
65*> \verbatim
66*> GL is DOUBLE PRECISION
67*> \endverbatim
68*>
69*> \param[in] GU
70*> \verbatim
71*> GU is DOUBLE PRECISION
72*> An upper and a lower bound on the eigenvalue.
73*> \endverbatim
74*>
75*> \param[in] D
76*> \verbatim
77*> D is DOUBLE PRECISION array, dimension (N)
78*> The n diagonal elements of the tridiagonal matrix T.
79*> \endverbatim
80*>
81*> \param[in] E2
82*> \verbatim
83*> E2 is DOUBLE PRECISION array, dimension (N-1)
84*> The (n-1) squared off-diagonal elements of the tridiagonal matrix T.
85*> \endverbatim
86*>
87*> \param[in] PIVMIN
88*> \verbatim
89*> PIVMIN is DOUBLE PRECISION
90*> The minimum pivot allowed in the Sturm sequence for T.
91*> \endverbatim
92*>
93*> \param[in] RELTOL
94*> \verbatim
95*> RELTOL is DOUBLE PRECISION
96*> The minimum relative width of an interval. When an interval
97*> is narrower than RELTOL times the larger (in
98*> magnitude) endpoint, then it is considered to be
99*> sufficiently small, i.e., converged. Note: this should
100*> always be at least radix*machine epsilon.
101*> \endverbatim
102*>
103*> \param[out] W
104*> \verbatim
105*> W is DOUBLE PRECISION
106*> \endverbatim
107*>
108*> \param[out] WERR
109*> \verbatim
110*> WERR is DOUBLE PRECISION
111*> The error bound on the corresponding eigenvalue approximation
112*> in W.
113*> \endverbatim
114*>
115*> \param[out] INFO
116*> \verbatim
117*> INFO is INTEGER
118*> = 0: Eigenvalue converged
119*> = -1: Eigenvalue did NOT converge
120*> \endverbatim
121*
122*> \par Internal Parameters:
123* =========================
124*>
125*> \verbatim
126*> FUDGE DOUBLE PRECISION, default = 2
127*> A "fudge factor" to widen the Gershgorin intervals.
128*> \endverbatim
129*
130* Authors:
131* ========
132*
133*> \author Univ. of Tennessee
134*> \author Univ. of California Berkeley
135*> \author Univ. of Colorado Denver
136*> \author NAG Ltd.
137*
138*> \ingroup larrk
139*
140* =====================================================================
141 SUBROUTINE dlarrk( N, IW, GL, GU,
142 $ D, E2, PIVMIN, RELTOL, W, WERR, INFO)
143*
144* -- LAPACK auxiliary routine --
145* -- LAPACK is a software package provided by Univ. of Tennessee, --
146* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
147*
148* .. Scalar Arguments ..
149 INTEGER INFO, IW, N
150 DOUBLE PRECISION PIVMIN, RELTOL, GL, GU, W, WERR
151* ..
152* .. Array Arguments ..
153 DOUBLE PRECISION D( * ), E2( * )
154* ..
155*
156* =====================================================================
157*
158* .. Parameters ..
159 DOUBLE PRECISION FUDGE, HALF, TWO, ZERO
160 parameter( half = 0.5d0, two = 2.0d0,
161 $ fudge = two, zero = 0.0d0 )
162* ..
163* .. Local Scalars ..
164 INTEGER I, IT, ITMAX, NEGCNT
165 DOUBLE PRECISION ATOLI, EPS, LEFT, MID, RIGHT, RTOLI, TMP1,
166 $ tmp2, tnorm
167* ..
168* .. External Functions ..
169 DOUBLE PRECISION DLAMCH
170 EXTERNAL dlamch
171* ..
172* .. Intrinsic Functions ..
173 INTRINSIC abs, int, log, max
174* ..
175* .. Executable Statements ..
176*
177* Quick return if possible
178*
179 IF( n.LE.0 ) THEN
180 info = 0
181 RETURN
182 END IF
183*
184* Get machine constants
185 eps = dlamch( 'P' )
186
187 tnorm = max( abs( gl ), abs( gu ) )
188 rtoli = reltol
189 atoli = fudge*two*pivmin
190
191 itmax = int( ( log( tnorm+pivmin )-log( pivmin ) ) /
192 $ log( two ) ) + 2
193
194 info = -1
195
196 left = gl - fudge*tnorm*eps*n - fudge*two*pivmin
197 right = gu + fudge*tnorm*eps*n + fudge*two*pivmin
198 it = 0
199
200 10 CONTINUE
201*
202* Check if interval converged or maximum number of iterations reached
203*
204 tmp1 = abs( right - left )
205 tmp2 = max( abs(right), abs(left) )
206 IF( tmp1.LT.max( atoli, pivmin, rtoli*tmp2 ) ) THEN
207 info = 0
208 GOTO 30
209 ENDIF
210 IF(it.GT.itmax)
211 $ GOTO 30
212
213*
214* Count number of negative pivots for mid-point
215*
216 it = it + 1
217 mid = half * (left + right)
218 negcnt = 0
219 tmp1 = d( 1 ) - mid
220 IF( abs( tmp1 ).LT.pivmin )
221 $ tmp1 = -pivmin
222 IF( tmp1.LE.zero )
223 $ negcnt = negcnt + 1
224*
225 DO 20 i = 2, n
226 tmp1 = d( i ) - e2( i-1 ) / tmp1 - mid
227 IF( abs( tmp1 ).LT.pivmin )
228 $ tmp1 = -pivmin
229 IF( tmp1.LE.zero )
230 $ negcnt = negcnt + 1
231 20 CONTINUE
232
233 IF(negcnt.GE.iw) THEN
234 right = mid
235 ELSE
236 left = mid
237 ENDIF
238 GOTO 10
239
240 30 CONTINUE
241*
242* Converged or maximum number of iterations reached
243*
244 w = half * (left + right)
245 werr = half * abs( right - left )
246
247 RETURN
248*
249* End of DLARRK
250*
251 END
subroutine dlarrk(n, iw, gl, gu, d, e2, pivmin, reltol, w, werr, info)
DLARRK computes one eigenvalue of a symmetric tridiagonal matrix T to suitable accuracy.
Definition dlarrk.f:143