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.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download SLARRR + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slarrr.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slarrr.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slarrr.f">
21 * SUBROUTINE SLARRR( N, D, E, INFO )
23 * .. Scalar Arguments ..
26 * .. Array Arguments ..
37 *> Perform tests to decide whether the symmetric tridiagonal matrix T
38 *> warrants expensive computations which guarantee high relative accuracy
39 *> in the eigenvalues.
48 *> The order of the matrix. N > 0.
53 *> D is REAL array, dimension (N)
54 *> The N diagonal elements of the tridiagonal matrix T.
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.
67 *> INFO = 0(default) : the matrix warrants computations preserving
69 *> INFO = 1 : the matrix warrants computations guaranteeing
70 *> only absolute accuracy.
76 *> \author Univ. of Tennessee
77 *> \author Univ. of California Berkeley
78 *> \author Univ. of Colorado Denver
81 *> \date September 2012
83 *> \ingroup OTHERauxiliary
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
94 * =====================================================================
95 SUBROUTINE SLARRR( N, D, E, INFO )
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..--
102 * .. Scalar Arguments ..
105 * .. Array Arguments ..
110 * =====================================================================
114 PARAMETER ( ZERO = 0.0E0,
115 $ RELCOND = 0.999E0 )
117 * .. Local Scalars ..
120 REAL EPS, SAFMIN, SMLNUM, RMIN, TMP, TMP2,
124 * .. External Functions ..
128 * .. Intrinsic Functions ..
131 * .. Executable Statements ..
133 * As a default, do NOT go for relative-accuracy preserving computations.
136 SAFMIN = SLAMCH( 'Safe minimum' )
137 EPS = SLAMCH( 'Precision' )
138 SMLNUM = SAFMIN / EPS
139 RMIN = SQRT( SMLNUM )
141 * Tests for relative accuracy
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
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
160 TMP = SQRT(ABS(D(1)))
161 IF (TMP.LT.RMIN) YESREL = .FALSE.
162 IF(.NOT.YESREL) GOTO 11
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
183 * *** MORE TO BE IMPLEMENTED ***
187 * Test if the lower bidiagonal matrix L from T = L D L^T
188 * (zero shift facto) is well conditioned
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)