1*> \brief \b SLASQ2 computes all the eigenvalues of the symmetric positive definite tridiagonal matrix associated with the qd Array Z to high relative accuracy. Used by sbdsqr and sstegr.
2*
3*  =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6*            http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download SLASQ2 + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slasq2.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slasq2.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slasq2.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18*  Definition:
19*  ===========
20*
21*       SUBROUTINE SLASQ2( N, Z, INFO )
22*
23*       .. Scalar Arguments ..
24*       INTEGER            INFO, N
25*       ..
26*       .. Array Arguments ..
27*       REAL               Z( * )
28*       ..
29*
30*
31*> \par Purpose:
32*  =============
33*>
34*> \verbatim
35*>
36*> SLASQ2 computes all the eigenvalues of the symmetric positive
37*> definite tridiagonal matrix associated with the qd array Z to high
38*> relative accuracy are computed to high relative accuracy, in the
39*> absence of denormalization, underflow and overflow.
40*>
41*> To see the relation of Z to the tridiagonal matrix, let L be a
42*> unit lower bidiagonal matrix with subdiagonals Z(2,4,6,,..) and
43*> let U be an upper bidiagonal matrix with 1's above and diagonal
44*> Z(1,3,5,,..). The tridiagonal is L*U or, if you prefer, the
45*> symmetric tridiagonal to which it is similar.
46*>
47*> Note : SLASQ2 defines a logical variable, IEEE, which is true
48*> on machines which follow ieee-754 floating-point standard in their
49*> handling of infinities and NaNs, and false otherwise. This variable
50*> is passed to SLASQ3.
51*> \endverbatim
52*
53*  Arguments:
54*  ==========
55*
56*> \param[in] N
57*> \verbatim
58*>          N is INTEGER
59*>        The number of rows and columns in the matrix. N >= 0.
60*> \endverbatim
61*>
62*> \param[in,out] Z
63*> \verbatim
64*>          Z is REAL array, dimension ( 4*N )
65*>        On entry Z holds the qd array. On exit, entries 1 to N hold
66*>        the eigenvalues in decreasing order, Z( 2*N+1 ) holds the
67*>        trace, and Z( 2*N+2 ) holds the sum of the eigenvalues. If
68*>        N > 2, then Z( 2*N+3 ) holds the iteration count, Z( 2*N+4 )
69*>        holds NDIVS/NIN^2, and Z( 2*N+5 ) holds the percentage of
70*>        shifts that failed.
71*> \endverbatim
72*>
73*> \param[out] INFO
74*> \verbatim
75*>          INFO is INTEGER
76*>        = 0: successful exit
77*>        < 0: if the i-th argument is a scalar and had an illegal
78*>             value, then INFO = -i, if the i-th argument is an
79*>             array and the j-entry had an illegal value, then
80*>             INFO = -(i*100+j)
81*>        > 0: the algorithm failed
82*>              = 1, a split was marked by a positive value in E
83*>              = 2, current block of Z not diagonalized after 100*N
84*>                   iterations (in inner while loop).  On exit Z holds
85*>                   a qd array with the same eigenvalues as the given Z.
86*>              = 3, termination criterion of outer while loop not met
87*>                   (program created more than N unreduced blocks)
88*> \endverbatim
89*
90*  Authors:
91*  ========
92*
93*> \author Univ. of Tennessee
94*> \author Univ. of California Berkeley
95*> \author Univ. of Colorado Denver
96*> \author NAG Ltd.
97*
98*> \date September 2012
99*
100*> \ingroup auxOTHERcomputational
101*
102*> \par Further Details:
103*  =====================
104*>
105*> \verbatim
106*>
107*>  Local Variables: I0:N0 defines a current unreduced segment of Z.
108*>  The shifts are accumulated in SIGMA. Iteration count is in ITER.
109*>  Ping-pong is controlled by PP (alternates between 0 and 1).
110*> \endverbatim
111*>
112*  =====================================================================
113      SUBROUTINE SLASQ2( N, Z, INFO )
114*
115*  -- LAPACK computational routine (version 3.4.2) --
116*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
117*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
118*     September 2012
119*
120*     .. Scalar Arguments ..
121      INTEGER            INFO, N
122*     ..
123*     .. Array Arguments ..
124      REAL               Z( * )
125*     ..
126*
127*  =====================================================================
128*
129*     .. Parameters ..
130      REAL               CBIAS
131      PARAMETER          ( CBIAS = 1.50E0 )
132      REAL               ZERO, HALF, ONE, TWO, FOUR, HUNDRD
133      PARAMETER          ( ZERO = 0.0E0, HALF = 0.5E0, ONE = 1.0E0,
134     $                     TWO = 2.0E0, FOUR = 4.0E0, HUNDRD = 100.0E0 )
135*     ..
136*     .. Local Scalars ..
137      LOGICAL            IEEE
138      INTEGER            I0, I4, IINFO, IPN4, ITER, IWHILA, IWHILB, K,
139     $                   KMIN, N0, NBIG, NDIV, NFAIL, PP, SPLT, TTYPE,
140     $                   I1, N1
141      REAL               D, DEE, DEEMIN, DESIG, DMIN, DMIN1, DMIN2, DN,
142     $                   DN1, DN2, E, EMAX, EMIN, EPS, G, OLDEMN, QMAX,
143     $                   QMIN, S, SAFMIN, SIGMA, T, TAU, TEMP, TOL,
144     $                   TOL2, TRACE, ZMAX, TEMPE, TEMPQ
145*     ..
146*     .. External Subroutines ..
147      EXTERNAL           SLASQ3, SLASRT, XERBLA
148*     ..
149*     .. External Functions ..
150      INTEGER            ILAENV
151      REAL               SLAMCH
152      EXTERNAL           ILAENV, SLAMCH
153*     ..
154*     .. Intrinsic Functions ..
155      INTRINSIC          ABS, MAX, MIN, REAL, SQRT
156*     ..
157*     .. Executable Statements ..
158*
159*     Test the input arguments.
160*     (in case SLASQ2 is not called by SLASQ1)
161*
162      INFO = 0
163      EPS = SLAMCH( 'Precision' )
164      SAFMIN = SLAMCH( 'Safe minimum' )
165      TOL = EPS*HUNDRD
166      TOL2 = TOL**2
167*
168      IF( N.LT.0 ) THEN
169         INFO = -1
170         CALL XERBLA( 'SLASQ2', 1 )
171         RETURN
172      ELSE IF( N.EQ.0 ) THEN
173         RETURN
174      ELSE IF( N.EQ.1 ) THEN
175*
176*        1-by-1 case.
177*
178         IF( Z( 1 ).LT.ZERO ) THEN
179            INFO = -201
180            CALL XERBLA( 'SLASQ2', 2 )
181         END IF
182         RETURN
183      ELSE IF( N.EQ.2 ) THEN
184*
185*        2-by-2 case.
186*
187         IF( Z( 2 ).LT.ZERO .OR. Z( 3 ).LT.ZERO ) THEN
188            INFO = -2
189            CALL XERBLA( 'SLASQ2', 2 )
190            RETURN
191         ELSE IF( Z( 3 ).GT.Z( 1 ) ) THEN
192            D = Z( 3 )
193            Z( 3 ) = Z( 1 )
194            Z( 1 ) = D
195         END IF
196         Z( 5 ) = Z( 1 ) + Z( 2 ) + Z( 3 )
197         IF( Z( 2 ).GT.Z( 3 )*TOL2 ) THEN
198            T = HALF*( ( Z( 1 )-Z( 3 ) )+Z( 2 ) )
199            S = Z( 3 )*( Z( 2 ) / T )
200            IF( S.LE.T ) THEN
201               S = Z( 3 )*( Z( 2 ) / ( T*( ONE+SQRT( ONE+S / T ) ) ) )
202            ELSE
203               S = Z( 3 )*( Z( 2 ) / ( T+SQRT( T )*SQRT( T+S ) ) )
204            END IF
205            T = Z( 1 ) + ( S+Z( 2 ) )
206            Z( 3 ) = Z( 3 )*( Z( 1 ) / T )
207            Z( 1 ) = T
208         END IF
209         Z( 2 ) = Z( 3 )
210         Z( 6 ) = Z( 2 ) + Z( 1 )
211         RETURN
212      END IF
213*
214*     Check for negative data and compute sums of q's and e's.
215*
216      Z( 2*N ) = ZERO
217      EMIN = Z( 2 )
218      QMAX = ZERO
219      ZMAX = ZERO
220      D = ZERO
221      E = ZERO
222*
223      DO 10 K = 1, 2*( N-1 ), 2
224         IF( Z( K ).LT.ZERO ) THEN
225            INFO = -( 200+K )
226            CALL XERBLA( 'SLASQ2', 2 )
227            RETURN
228         ELSE IF( Z( K+1 ).LT.ZERO ) THEN
229            INFO = -( 200+K+1 )
230            CALL XERBLA( 'SLASQ2', 2 )
231            RETURN
232         END IF
233         D = D + Z( K )
234         E = E + Z( K+1 )
235         QMAX = MAX( QMAX, Z( K ) )
236         EMIN = MIN( EMIN, Z( K+1 ) )
237         ZMAX = MAX( QMAX, ZMAX, Z( K+1 ) )
238   10 CONTINUE
239      IF( Z( 2*N-1 ).LT.ZERO ) THEN
240         INFO = -( 200+2*N-1 )
241         CALL XERBLA( 'SLASQ2', 2 )
242         RETURN
243      END IF
244      D = D + Z( 2*N-1 )
245      QMAX = MAX( QMAX, Z( 2*N-1 ) )
246      ZMAX = MAX( QMAX, ZMAX )
247*
248*     Check for diagonality.
249*
250      IF( E.EQ.ZERO ) THEN
251         DO 20 K = 2, N
252            Z( K ) = Z( 2*K-1 )
253   20    CONTINUE
254         CALL SLASRT( 'D', N, Z, IINFO )
255         Z( 2*N-1 ) = D
256         RETURN
257      END IF
258*
259      TRACE = D + E
260*
261*     Check for zero data.
262*
263      IF( TRACE.EQ.ZERO ) THEN
264         Z( 2*N-1 ) = ZERO
265         RETURN
266      END IF
267*
268*     Check whether the machine is IEEE conformable.
269*
270*     IEEE = ILAENV( 10, 'SLASQ2', 'N', 1, 2, 3, 4 ).EQ.1 .AND.
271*    $       ILAENV( 11, 'SLASQ2', 'N', 1, 2, 3, 4 ).EQ.1
272*
273*     [11/15/2008] The case IEEE=.TRUE. has a problem in single precision with
274*     some the test matrices of type 16. The double precision code is fine.
275*
276      IEEE = .FALSE.
277*
278*     Rearrange data for locality: Z=(q1,qq1,e1,ee1,q2,qq2,e2,ee2,...).
279*
280      DO 30 K = 2*N, 2, -2
281         Z( 2*K ) = ZERO
282         Z( 2*K-1 ) = Z( K )
283         Z( 2*K-2 ) = ZERO
284         Z( 2*K-3 ) = Z( K-1 )
285   30 CONTINUE
286*
287      I0 = 1
288      N0 = N
289*
290*     Reverse the qd-array, if warranted.
291*
292      IF( CBIAS*Z( 4*I0-3 ).LT.Z( 4*N0-3 ) ) THEN
293         IPN4 = 4*( I0+N0 )
294         DO 40 I4 = 4*I0, 2*( I0+N0-1 ), 4
295            TEMP = Z( I4-3 )
296            Z( I4-3 ) = Z( IPN4-I4-3 )
297            Z( IPN4-I4-3 ) = TEMP
298            TEMP = Z( I4-1 )
299            Z( I4-1 ) = Z( IPN4-I4-5 )
300            Z( IPN4-I4-5 ) = TEMP
301   40    CONTINUE
302      END IF
303*
304*     Initial split checking via dqd and Li's test.
305*
306      PP = 0
307*
308      DO 80 K = 1, 2
309*
310         D = Z( 4*N0+PP-3 )
311         DO 50 I4 = 4*( N0-1 ) + PP, 4*I0 + PP, -4
312            IF( Z( I4-1 ).LE.TOL2*D ) THEN
313               Z( I4-1 ) = -ZERO
314               D = Z( I4-3 )
315            ELSE
316               D = Z( I4-3 )*( D / ( D+Z( I4-1 ) ) )
317            END IF
318   50    CONTINUE
319*
320*        dqd maps Z to ZZ plus Li's test.
321*
322         EMIN = Z( 4*I0+PP+1 )
323         D = Z( 4*I0+PP-3 )
324         DO 60 I4 = 4*I0 + PP, 4*( N0-1 ) + PP, 4
325            Z( I4-2*PP-2 ) = D + Z( I4-1 )
326            IF( Z( I4-1 ).LE.TOL2*D ) THEN
327               Z( I4-1 ) = -ZERO
328               Z( I4-2*PP-2 ) = D
329               Z( I4-2*PP ) = ZERO
330               D = Z( I4+1 )
331            ELSE IF( SAFMIN*Z( I4+1 ).LT.Z( I4-2*PP-2 ) .AND.
332     $               SAFMIN*Z( I4-2*PP-2 ).LT.Z( I4+1 ) ) THEN
333               TEMP = Z( I4+1 ) / Z( I4-2*PP-2 )
334               Z( I4-2*PP ) = Z( I4-1 )*TEMP
335               D = D*TEMP
336            ELSE
337               Z( I4-2*PP ) = Z( I4+1 )*( Z( I4-1 ) / Z( I4-2*PP-2 ) )
338               D = Z( I4+1 )*( D / Z( I4-2*PP-2 ) )
339            END IF
340            EMIN = MIN( EMIN, Z( I4-2*PP ) )
341   60    CONTINUE
342         Z( 4*N0-PP-2 ) = D
343*
344*        Now find qmax.
345*
346         QMAX = Z( 4*I0-PP-2 )
347         DO 70 I4 = 4*I0 - PP + 2, 4*N0 - PP - 2, 4
348            QMAX = MAX( QMAX, Z( I4 ) )
349   70    CONTINUE
350*
351*        Prepare for the next iteration on K.
352*
353         PP = 1 - PP
354   80 CONTINUE
355*
356*     Initialise variables to pass to SLASQ3.
357*
358      TTYPE = 0
359      DMIN1 = ZERO
360      DMIN2 = ZERO
361      DN    = ZERO
362      DN1   = ZERO
363      DN2   = ZERO
364      G     = ZERO
365      TAU   = ZERO
366*
367      ITER = 2
368      NFAIL = 0
369      NDIV = 2*( N0-I0 )
370*
371      DO 160 IWHILA = 1, N + 1
372         IF( N0.LT.1 )
373     $      GO TO 170
374*
375*        While array unfinished do
376*
377*        E(N0) holds the value of SIGMA when submatrix in I0:N0
378*        splits from the rest of the array, but is negated.
379*
380         DESIG = ZERO
381         IF( N0.EQ.N ) THEN
382            SIGMA = ZERO
383         ELSE
384            SIGMA = -Z( 4*N0-1 )
385         END IF
386         IF( SIGMA.LT.ZERO ) THEN
387            INFO = 1
388            RETURN
389         END IF
390*
391*        Find last unreduced submatrix's top index I0, find QMAX and
392*        EMIN. Find Gershgorin-type bound if Q's much greater than E's.
393*
394         EMAX = ZERO
395         IF( N0.GT.I0 ) THEN
396            EMIN = ABS( Z( 4*N0-5 ) )
397         ELSE
398            EMIN = ZERO
399         END IF
400         QMIN = Z( 4*N0-3 )
401         QMAX = QMIN
402         DO 90 I4 = 4*N0, 8, -4
403            IF( Z( I4-5 ).LE.ZERO )
404     $         GO TO 100
405            IF( QMIN.GE.FOUR*EMAX ) THEN
406               QMIN = MIN( QMIN, Z( I4-3 ) )
407               EMAX = MAX( EMAX, Z( I4-5 ) )
408            END IF
409            QMAX = MAX( QMAX, Z( I4-7 )+Z( I4-5 ) )
410            EMIN = MIN( EMIN, Z( I4-5 ) )
411   90    CONTINUE
412         I4 = 4
413*
414  100    CONTINUE
415         I0 = I4 / 4
416         PP = 0
417*
418         IF( N0-I0.GT.1 ) THEN
419            DEE = Z( 4*I0-3 )
420            DEEMIN = DEE
421            KMIN = I0
422            DO 110 I4 = 4*I0+1, 4*N0-3, 4
423               DEE = Z( I4 )*( DEE /( DEE+Z( I4-2 ) ) )
424               IF( DEE.LE.DEEMIN ) THEN
425                  DEEMIN = DEE
426                  KMIN = ( I4+3 )/4
427               END IF
428  110       CONTINUE
429            IF( (KMIN-I0)*2.LT.N0-KMIN .AND.
430     $         DEEMIN.LE.HALF*Z(4*N0-3) ) THEN
431               IPN4 = 4*( I0+N0 )
432               PP = 2
433               DO 120 I4 = 4*I0, 2*( I0+N0-1 ), 4
434                  TEMP = Z( I4-3 )
435                  Z( I4-3 ) = Z( IPN4-I4-3 )
436                  Z( IPN4-I4-3 ) = TEMP
437                  TEMP = Z( I4-2 )
438                  Z( I4-2 ) = Z( IPN4-I4-2 )
439                  Z( IPN4-I4-2 ) = TEMP
440                  TEMP = Z( I4-1 )
441                  Z( I4-1 ) = Z( IPN4-I4-5 )
442                  Z( IPN4-I4-5 ) = TEMP
443                  TEMP = Z( I4 )
444                  Z( I4 ) = Z( IPN4-I4-4 )
445                  Z( IPN4-I4-4 ) = TEMP
446  120          CONTINUE
447            END IF
448         END IF
449*
450*        Put -(initial shift) into DMIN.
451*
452         DMIN = -MAX( ZERO, QMIN-TWO*SQRT( QMIN )*SQRT( EMAX ) )
453*
454*        Now I0:N0 is unreduced.
455*        PP = 0 for ping, PP = 1 for pong.
456*        PP = 2 indicates that flipping was applied to the Z array and
457*               and that the tests for deflation upon entry in SLASQ3
458*               should not be performed.
459*
460         NBIG = 100*( N0-I0+1 )
461         DO 140 IWHILB = 1, NBIG
462            IF( I0.GT.N0 )
463     $         GO TO 150
464*
465*           While submatrix unfinished take a good dqds step.
466*
467            CALL SLASQ3( I0, N0, Z, PP, DMIN, SIGMA, DESIG, QMAX, NFAIL,
468     $                   ITER, NDIV, IEEE, TTYPE, DMIN1, DMIN2, DN, DN1,
469     $                   DN2, G, TAU )
470*
471            PP = 1 - PP
472*
473*           When EMIN is very small check for splits.
474*
475            IF( PP.EQ.0 .AND. N0-I0.GE.3 ) THEN
476               IF( Z( 4*N0 ).LE.TOL2*QMAX .OR.
477     $             Z( 4*N0-1 ).LE.TOL2*SIGMA ) THEN
478                  SPLT = I0 - 1
479                  QMAX = Z( 4*I0-3 )
480                  EMIN = Z( 4*I0-1 )
481                  OLDEMN = Z( 4*I0 )
482                  DO 130 I4 = 4*I0, 4*( N0-3 ), 4
483                     IF( Z( I4 ).LE.TOL2*Z( I4-3 ) .OR.
484     $                   Z( I4-1 ).LE.TOL2*SIGMA ) THEN
485                        Z( I4-1 ) = -SIGMA
486                        SPLT = I4 / 4
487                        QMAX = ZERO
488                        EMIN = Z( I4+3 )
489                        OLDEMN = Z( I4+4 )
490                     ELSE
491                        QMAX = MAX( QMAX, Z( I4+1 ) )
492                        EMIN = MIN( EMIN, Z( I4-1 ) )
493                        OLDEMN = MIN( OLDEMN, Z( I4 ) )
494                     END IF
495  130             CONTINUE
496                  Z( 4*N0-1 ) = EMIN
497                  Z( 4*N0 ) = OLDEMN
498                  I0 = SPLT + 1
499               END IF
500            END IF
501*
502  140    CONTINUE
503*
504         INFO = 2
505*
506*        Maximum number of iterations exceeded, restore the shift
507*        SIGMA and place the new d's and e's in a qd array.
508*        This might need to be done for several blocks
509*
510         I1 = I0
511         N1 = N0
512 145     CONTINUE
513         TEMPQ = Z( 4*I0-3 )
514         Z( 4*I0-3 ) = Z( 4*I0-3 ) + SIGMA
515         DO K = I0+1, N0
516            TEMPE = Z( 4*K-5 )
517            Z( 4*K-5 ) = Z( 4*K-5 ) * (TEMPQ / Z( 4*K-7 ))
518            TEMPQ = Z( 4*K-3 )
519            Z( 4*K-3 ) = Z( 4*K-3 ) + SIGMA + TEMPE - Z( 4*K-5 )
520         END DO
521*
522*        Prepare to do this on the previous block if there is one
523*
524         IF( I1.GT.1 ) THEN
525            N1 = I1-1
526            DO WHILE( ( I1.GE.2 ) .AND. ( Z(4*I1-5).GE.ZERO ) )
527               I1 = I1 - 1
528            END DO
529            IF( I1.GE.1 ) THEN
530               SIGMA = -Z(4*N1-1)
531               GO TO 145
532            END IF
533         END IF
534
535         DO K = 1, N
536            Z( 2*K-1 ) = Z( 4*K-3 )
537*
538*        Only the block 1..N0 is unfinished.  The rest of the e's
539*        must be essentially zero, although sometimes other data
540*        has been stored in them.
541*
542            IF( K.LT.N0 ) THEN
543               Z( 2*K ) = Z( 4*K-1 )
544            ELSE
545               Z( 2*K ) = 0
546            END IF
547         END DO
548         RETURN
549*
550*        end IWHILB
551*
552  150    CONTINUE
553*
554  160 CONTINUE
555*
556      INFO = 3
557      RETURN
558*
559*     end IWHILA
560*
561  170 CONTINUE
562*
563*     Move q's to the front.
564*
565      DO 180 K = 2, N
566         Z( K ) = Z( 4*K-3 )
567  180 CONTINUE
568*
569*     Sort and compute sum of eigenvalues.
570*
571      CALL SLASRT( 'D', N, Z, IINFO )
572*
573      E = ZERO
574      DO 190 K = N, 1, -1
575         E = E + Z( K )
576  190 CONTINUE
577*
578*     Store trace, sum(eigenvalues) and information on performance.
579*
580      Z( 2*N+1 ) = TRACE
581      Z( 2*N+2 ) = E
582      Z( 2*N+3 ) = REAL( ITER )
583      Z( 2*N+4 ) = REAL( NDIV ) / REAL( N**2 )
584      Z( 2*N+5 ) = HUNDRD*NFAIL / REAL( ITER )
585      RETURN
586*
587*     End of SLASQ2
588*
589      END
590