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