LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
slarrr.f
Go to the documentation of this file.
1*> \brief \b SLARRR performs tests to decide whether the symmetric tridiagonal matrix T warrants expensive computations which guarantee high relative accuracy in the eigenvalues.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download SLARRR + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slarrr.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slarrr.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slarrr.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE SLARRR( N, D, E, INFO )
20*
21* .. Scalar Arguments ..
22* INTEGER N, INFO
23* ..
24* .. Array Arguments ..
25* REAL D( * ), E( * )
26* ..
27*
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> Perform tests to decide whether the symmetric tridiagonal matrix T
36*> warrants expensive computations which guarantee high relative accuracy
37*> in the eigenvalues.
38*> \endverbatim
39*
40* Arguments:
41* ==========
42*
43*> \param[in] N
44*> \verbatim
45*> N is INTEGER
46*> The order of the matrix. N > 0.
47*> \endverbatim
48*>
49*> \param[in] D
50*> \verbatim
51*> D is REAL array, dimension (N)
52*> The N diagonal elements of the tridiagonal matrix T.
53*> \endverbatim
54*>
55*> \param[in,out] E
56*> \verbatim
57*> E is REAL array, dimension (N)
58*> On entry, the first (N-1) entries contain the subdiagonal
59*> elements of the tridiagonal matrix T; E(N) is set to ZERO.
60*> \endverbatim
61*>
62*> \param[out] INFO
63*> \verbatim
64*> INFO is INTEGER
65*> INFO = 0(default) : the matrix warrants computations preserving
66*> relative accuracy.
67*> INFO = 1 : the matrix warrants computations guaranteeing
68*> only absolute accuracy.
69*> \endverbatim
70*
71* Authors:
72* ========
73*
74*> \author Univ. of Tennessee
75*> \author Univ. of California Berkeley
76*> \author Univ. of Colorado Denver
77*> \author NAG Ltd.
78*
79*> \ingroup larrr
80*
81*> \par Contributors:
82* ==================
83*>
84*> Beresford Parlett, University of California, Berkeley, USA \n
85*> Jim Demmel, University of California, Berkeley, USA \n
86*> Inderjit Dhillon, University of Texas, Austin, USA \n
87*> Osni Marques, LBNL/NERSC, USA \n
88*> Christof Voemel, University of California, Berkeley, USA
89*
90* =====================================================================
91 SUBROUTINE slarrr( N, D, E, INFO )
92*
93* -- LAPACK auxiliary routine --
94* -- LAPACK is a software package provided by Univ. of Tennessee, --
95* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
96*
97* .. Scalar Arguments ..
98 INTEGER N, INFO
99* ..
100* .. Array Arguments ..
101 REAL D( * ), E( * )
102* ..
103*
104*
105* =====================================================================
106*
107* .. Parameters ..
108 REAL ZERO, RELCOND
109 parameter( zero = 0.0e0,
110 $ relcond = 0.999e0 )
111* ..
112* .. Local Scalars ..
113 INTEGER I
114 LOGICAL YESREL
115 REAL EPS, SAFMIN, SMLNUM, RMIN, TMP, TMP2,
116 $ OFFDIG, OFFDIG2
117
118* ..
119* .. External Functions ..
120 REAL SLAMCH
121 EXTERNAL slamch
122* ..
123* .. Intrinsic Functions ..
124 INTRINSIC abs
125* ..
126* .. Executable Statements ..
127*
128* Quick return if possible
129*
130 IF( n.LE.0 ) THEN
131 info = 0
132 RETURN
133 END IF
134*
135* As a default, do NOT go for relative-accuracy preserving computations.
136 info = 1
137
138 safmin = slamch( 'Safe minimum' )
139 eps = slamch( 'Precision' )
140 smlnum = safmin / eps
141 rmin = sqrt( smlnum )
142
143* Tests for relative accuracy
144*
145* Test for scaled diagonal dominance
146* Scale the diagonal entries to one and check whether the sum of the
147* off-diagonals is less than one
148*
149* The sdd relative error bounds have a 1/(1- 2*x) factor in them,
150* x = max(OFFDIG + OFFDIG2), so when x is close to 1/2, no relative
151* accuracy is promised. In the notation of the code fragment below,
152* 1/(1 - (OFFDIG + OFFDIG2)) is the condition number.
153* We don't think it is worth going into "sdd mode" unless the relative
154* condition number is reasonable, not 1/macheps.
155* The threshold should be compatible with other thresholds used in the
156* code. We set OFFDIG + OFFDIG2 <= .999 =: RELCOND, it corresponds
157* to losing at most 3 decimal digits: 1 / (1 - (OFFDIG + OFFDIG2)) <= 1000
158* instead of the current OFFDIG + OFFDIG2 < 1
159*
160 yesrel = .true.
161 offdig = zero
162 tmp = sqrt(abs(d(1)))
163 IF (tmp.LT.rmin) yesrel = .false.
164 IF(.NOT.yesrel) GOTO 11
165 DO 10 i = 2, n
166 tmp2 = sqrt(abs(d(i)))
167 IF (tmp2.LT.rmin) yesrel = .false.
168 IF(.NOT.yesrel) GOTO 11
169 offdig2 = abs(e(i-1))/(tmp*tmp2)
170 IF(offdig+offdig2.GE.relcond) yesrel = .false.
171 IF(.NOT.yesrel) GOTO 11
172 tmp = tmp2
173 offdig = offdig2
174 10 CONTINUE
175 11 CONTINUE
176
177 IF( yesrel ) THEN
178 info = 0
179 RETURN
180 ELSE
181 ENDIF
182*
183
184*
185* *** MORE TO BE IMPLEMENTED ***
186*
187
188*
189* Test if the lower bidiagonal matrix L from T = L D L^T
190* (zero shift facto) is well conditioned
191*
192
193*
194* Test if the upper bidiagonal matrix U from T = U D U^T
195* (zero shift facto) is well conditioned.
196* In this case, the matrix needs to be flipped and, at the end
197* of the eigenvector computation, the flip needs to be applied
198* to the computed eigenvectors (and the support)
199*
200
201*
202 RETURN
203*
204* End of SLARRR
205*
206 END
subroutine slarrr(n, d, e, info)
SLARRR performs tests to decide whether the symmetric tridiagonal matrix T warrants expensive computa...
Definition slarrr.f:92