LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
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 September 2012
82 *
83 *> \ingroup auxOTHERauxiliary
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.4.2) --
98 * -- LAPACK is a software package provided by Univ. of Tennessee, --
99 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
100 * September 2012
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 * As a default, do NOT go for relative-accuracy preserving computations.
134  info = 1
135 
136  safmin = slamch( 'Safe minimum' )
137  eps = slamch( 'Precision' )
138  smlnum = safmin / eps
139  rmin = sqrt( smlnum )
140 
141 * Tests for relative accuracy
142 *
143 * Test for scaled diagonal dominance
144 * Scale the diagonal entries to one and check whether the sum of the
145 * off-diagonals is less than one
146 *
147 * The sdd relative error bounds have a 1/(1- 2*x) factor in them,
148 * x = max(OFFDIG + OFFDIG2), so when x is close to 1/2, no relative
149 * accuracy is promised. In the notation of the code fragment below,
150 * 1/(1 - (OFFDIG + OFFDIG2)) is the condition number.
151 * We don't think it is worth going into "sdd mode" unless the relative
152 * condition number is reasonable, not 1/macheps.
153 * The threshold should be compatible with other thresholds used in the
154 * code. We set OFFDIG + OFFDIG2 <= .999 =: RELCOND, it corresponds
155 * to losing at most 3 decimal digits: 1 / (1 - (OFFDIG + OFFDIG2)) <= 1000
156 * instead of the current OFFDIG + OFFDIG2 < 1
157 *
158  yesrel = .true.
159  offdig = zero
160  tmp = sqrt(abs(d(1)))
161  IF (tmp.LT.rmin) yesrel = .false.
162  IF(.NOT.yesrel) goto 11
163  DO 10 i = 2, n
164  tmp2 = sqrt(abs(d(i)))
165  IF (tmp2.LT.rmin) yesrel = .false.
166  IF(.NOT.yesrel) goto 11
167  offdig2 = abs(e(i-1))/(tmp*tmp2)
168  IF(offdig+offdig2.GE.relcond) yesrel = .false.
169  IF(.NOT.yesrel) goto 11
170  tmp = tmp2
171  offdig = offdig2
172  10 continue
173  11 continue
174 
175  IF( yesrel ) THEN
176  info = 0
177  return
178  ELSE
179  ENDIF
180 *
181 
182 *
183 * *** MORE TO BE IMPLEMENTED ***
184 *
185 
186 *
187 * Test if the lower bidiagonal matrix L from T = L D L^T
188 * (zero shift facto) is well conditioned
189 *
190 
191 *
192 * Test if the upper bidiagonal matrix U from T = U D U^T
193 * (zero shift facto) is well conditioned.
194 * In this case, the matrix needs to be flipped and, at the end
195 * of the eigenvector computation, the flip needs to be applied
196 * to the computed eigenvectors (and the support)
197 *
198 
199 *
200  return
201 *
202 * END OF SLARRR
203 *
204  END