1 *> \brief \b DLAED6 used by sstedc. Computes one Newton step in solution of the secular equation.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download DLAED6 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlaed6.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlaed6.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaed6.f">
21 * SUBROUTINE DLAED6( KNITER, ORGATI, RHO, D, Z, FINIT, TAU, INFO )
23 * .. Scalar Arguments ..
25 * INTEGER INFO, KNITER
26 * DOUBLE PRECISION FINIT, RHO, TAU
28 * .. Array Arguments ..
29 * DOUBLE PRECISION D( 3 ), Z( 3 )
38 *> DLAED6 computes the positive or negative root (closest to the origin)
41 *> f(x) = rho + --------- + ---------- + ---------
42 *> d(1)-x d(2)-x d(3)-x
46 *> if ORGATI = .true. the root is between d(2) and d(3);
47 *> otherwise it is between d(1) and d(2)
49 *> This routine will be called by DLAED4 when necessary. In most cases,
50 *> the root sought is the smallest in magnitude, though it might not be
51 *> in some extremely rare situations.
60 *> Refer to DLAED4 for its significance.
66 *> If ORGATI is true, the needed root is between d(2) and
67 *> d(3); otherwise it is between d(1) and d(2). See
68 *> DLAED4 for further details.
73 *> RHO is DOUBLE PRECISION
74 *> Refer to the equation f(x) above.
79 *> D is DOUBLE PRECISION array, dimension (3)
80 *> D satisfies d(1) < d(2) < d(3).
85 *> Z is DOUBLE PRECISION array, dimension (3)
86 *> Each of the elements in z must be positive.
91 *> FINIT is DOUBLE PRECISION
92 *> The value of f at 0. It is more accurate than the one
93 *> evaluated inside this routine (if someone wants to do
99 *> TAU is DOUBLE PRECISION
100 *> The root of the equation f(x).
106 *> = 0: successful exit
107 *> > 0: if INFO = 1, failure to converge
113 *> \author Univ. of Tennessee
114 *> \author Univ. of California Berkeley
115 *> \author Univ. of Colorado Denver
118 *> \date November 2015
120 *> \ingroup auxOTHERcomputational
122 *> \par Further Details:
123 * =====================
127 *> 10/02/03: This version has a few statements commented out for thread
128 *> safety (machine parameters are computed on each entry). SJH.
130 *> 05/10/06: Modified from a new version of Ren-Cang Li, use
131 *> Gragg-Thornton-Warner cubic convergent scheme for better stability.
134 *> \par Contributors:
137 *> Ren-Cang Li, Computer Science Division, University of California
140 * =====================================================================
141 SUBROUTINE DLAED6( KNITER, ORGATI, RHO, D, Z, FINIT, TAU, INFO )
143 * -- LAPACK computational routine (version 3.6.0) --
144 * -- LAPACK is a software package provided by Univ. of Tennessee, --
145 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
148 * .. Scalar Arguments ..
151 DOUBLE PRECISION FINIT, RHO, TAU
153 * .. Array Arguments ..
154 DOUBLE PRECISION D( 3 ), Z( 3 )
157 * =====================================================================
161 PARAMETER ( MAXIT = 40 )
162 DOUBLE PRECISION ZERO, ONE, TWO, THREE, FOUR, EIGHT
163 PARAMETER ( ZERO = 0.0D0, ONE = 1.0D0, TWO = 2.0D0,
164 $ THREE = 3.0D0, FOUR = 4.0D0, EIGHT = 8.0D0 )
166 * .. External Functions ..
167 DOUBLE PRECISION DLAMCH
171 DOUBLE PRECISION DSCALE( 3 ), ZSCALE( 3 )
173 * .. Local Scalars ..
175 INTEGER I, ITER, NITER
176 DOUBLE PRECISION A, B, BASE, C, DDF, DF, EPS, ERRETM, ETA, F,
177 $ FC, SCLFAC, SCLINV, SMALL1, SMALL2, SMINV1,
178 $ SMINV2, TEMP, TEMP1, TEMP2, TEMP3, TEMP4,
181 * .. Intrinsic Functions ..
182 INTRINSIC ABS, INT, LOG, MAX, MIN, SQRT
184 * .. Executable Statements ..
195 IF( FINIT .LT. ZERO )THEN
203 IF( KNITER.EQ.2 ) THEN
205 TEMP = ( D( 3 )-D( 2 ) ) / TWO
206 C = RHO + Z( 1 ) / ( ( D( 1 )-D( 2 ) )-TEMP )
207 A = C*( D( 2 )+D( 3 ) ) + Z( 2 ) + Z( 3 )
208 B = C*D( 2 )*D( 3 ) + Z( 2 )*D( 3 ) + Z( 3 )*D( 2 )
210 TEMP = ( D( 1 )-D( 2 ) ) / TWO
211 C = RHO + Z( 3 ) / ( ( D( 3 )-D( 2 ) )-TEMP )
212 A = C*( D( 1 )+D( 2 ) ) + Z( 1 ) + Z( 2 )
213 B = C*D( 1 )*D( 2 ) + Z( 1 )*D( 2 ) + Z( 2 )*D( 1 )
215 TEMP = MAX( ABS( A ), ABS( B ), ABS( C ) )
221 ELSE IF( A.LE.ZERO ) THEN
222 TAU = ( A-SQRT( ABS( A*A-FOUR*B*C ) ) ) / ( TWO*C )
224 TAU = TWO*B / ( A+SQRT( ABS( A*A-FOUR*B*C ) ) )
226 IF( TAU .LT. LBD .OR. TAU .GT. UBD )
227 $ TAU = ( LBD+UBD )/TWO
228 IF( D(1).EQ.TAU .OR. D(2).EQ.TAU .OR. D(3).EQ.TAU ) THEN
231 TEMP = FINIT + TAU*Z(1)/( D(1)*( D( 1 )-TAU ) ) +
232 $ TAU*Z(2)/( D(2)*( D( 2 )-TAU ) ) +
233 $ TAU*Z(3)/( D(3)*( D( 3 )-TAU ) )
234 IF( TEMP .LE. ZERO )THEN
239 IF( ABS( FINIT ).LE.ABS( TEMP ) )
244 * get machine parameters for possible scaling to avoid overflow
246 * modified by Sven: parameters SMALL1, SMINV1, SMALL2,
247 * SMINV2, EPS are not SAVEd anymore between one call to the
248 * others but recomputed at each call
250 EPS = DLAMCH( 'Epsilon' )
251 BASE = DLAMCH( 'Base' )
252 SMALL1 = BASE**( INT( LOG( DLAMCH( 'SafMin' ) ) / LOG( BASE ) /
254 SMINV1 = ONE / SMALL1
255 SMALL2 = SMALL1*SMALL1
256 SMINV2 = SMINV1*SMINV1
258 * Determine if scaling of inputs necessary to avoid overflow
259 * when computing 1/TEMP**3
262 TEMP = MIN( ABS( D( 2 )-TAU ), ABS( D( 3 )-TAU ) )
264 TEMP = MIN( ABS( D( 1 )-TAU ), ABS( D( 2 )-TAU ) )
267 IF( TEMP.LE.SMALL1 ) THEN
269 IF( TEMP.LE.SMALL2 ) THEN
271 * Scale up by power of radix nearest 1/SAFMIN**(2/3)
277 * Scale up by power of radix nearest 1/SAFMIN**(1/3)
283 * Scaling up safe because D, Z, TAU scaled elsewhere to be O(1)
286 DSCALE( I ) = D( I )*SCLFAC
287 ZSCALE( I ) = Z( I )*SCLFAC
294 * Copy D and Z to DSCALE and ZSCALE
306 TEMP = ONE / ( DSCALE( I )-TAU )
307 TEMP1 = ZSCALE( I )*TEMP
310 FC = FC + TEMP1 / DSCALE( I )
316 IF( ABS( F ).LE.ZERO )
318 IF( F .LE. ZERO )THEN
324 * Iteration begins -- Use Gragg-Thornton-Warner cubic convergent
327 * It is not hard to see that
329 * 1) Iterations will go up monotonically
332 * 2) Iterations will go down monotonically
337 DO 50 NITER = ITER, MAXIT
340 TEMP1 = DSCALE( 2 ) - TAU
341 TEMP2 = DSCALE( 3 ) - TAU
343 TEMP1 = DSCALE( 1 ) - TAU
344 TEMP2 = DSCALE( 2 ) - TAU
346 A = ( TEMP1+TEMP2 )*F - TEMP1*TEMP2*DF
348 C = F - ( TEMP1+TEMP2 )*DF + TEMP1*TEMP2*DDF
349 TEMP = MAX( ABS( A ), ABS( B ), ABS( C ) )
355 ELSE IF( A.LE.ZERO ) THEN
356 ETA = ( A-SQRT( ABS( A*A-FOUR*B*C ) ) ) / ( TWO*C )
358 ETA = TWO*B / ( A+SQRT( ABS( A*A-FOUR*B*C ) ) )
360 IF( F*ETA.GE.ZERO ) THEN
365 IF( TAU .LT. LBD .OR. TAU .GT. UBD )
366 $ TAU = ( LBD + UBD )/TWO
373 IF ( ( DSCALE( I )-TAU ).NE.ZERO ) THEN
374 TEMP = ONE / ( DSCALE( I )-TAU )
375 TEMP1 = ZSCALE( I )*TEMP
378 TEMP4 = TEMP1 / DSCALE( I )
380 ERRETM = ERRETM + ABS( TEMP4 )
388 ERRETM = EIGHT*( ABS( FINIT )+ABS( TAU )*ERRETM ) +
390 IF( ( ABS( F ).LE.FOUR*EPS*ERRETM ) .OR.
391 $ ( (UBD-LBD).LE.FOUR*EPS*ABS(TAU) ) )
393 IF( F .LE. ZERO )THEN