LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dlasq2()

subroutine dlasq2 ( integer n,
double precision, dimension( * ) z,
integer info )

DLASQ2 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.

Download DLASQ2 + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> DLASQ2 computes all the eigenvalues of the symmetric positive
!> definite tridiagonal matrix associated with the qd array Z to high
!> relative accuracy are computed to high relative accuracy, in the
!> absence of denormalization, underflow and overflow.
!>
!> To see the relation of Z to the tridiagonal matrix, let L be a
!> unit lower bidiagonal matrix with subdiagonals Z(2,4,6,,..) and
!> let U be an upper bidiagonal matrix with 1's above and diagonal
!> Z(1,3,5,,..). The tridiagonal is L*U or, if you prefer, the
!> symmetric tridiagonal to which it is similar.
!>
!> Note : DLASQ2 defines a logical variable, IEEE, which is true
!> on machines which follow ieee-754 floating-point standard in their
!> handling of infinities and NaNs, and false otherwise. This variable
!> is passed to DLASQ3.
!> 
Parameters
[in]N
!>          N is INTEGER
!>        The number of rows and columns in the matrix. N >= 0.
!> 
[in,out]Z
!>          Z is DOUBLE PRECISION array, dimension ( 4*N )
!>        On entry Z holds the qd array. On exit, entries 1 to N hold
!>        the eigenvalues in decreasing order, Z( 2*N+1 ) holds the
!>        trace, and Z( 2*N+2 ) holds the sum of the eigenvalues. If
!>        N > 2, then Z( 2*N+3 ) holds the iteration count, Z( 2*N+4 )
!>        holds NDIVS/NIN^2, and Z( 2*N+5 ) holds the percentage of
!>        shifts that failed.
!> 
[out]INFO
!>          INFO is INTEGER
!>        = 0: successful exit
!>        < 0: if the i-th argument is a scalar and had an illegal
!>             value, then INFO = -i, if the i-th argument is an
!>             array and the j-entry had an illegal value, then
!>             INFO = -(i*100+j)
!>        > 0: the algorithm failed
!>              = 1, a split was marked by a positive value in E
!>              = 2, current block of Z not diagonalized after 100*N
!>                   iterations (in inner while loop).  On exit Z holds
!>                   a qd array with the same eigenvalues as the given Z.
!>              = 3, termination criterion of outer while loop not met
!>                   (program created more than N unreduced blocks)
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
!>
!>  Local Variables: I0:N0 defines a current unreduced segment of Z.
!>  The shifts are accumulated in SIGMA. Iteration count is in ITER.
!>  Ping-pong is controlled by PP (alternates between 0 and 1).
!> 

Definition at line 109 of file dlasq2.f.

110*
111* -- LAPACK computational routine --
112* -- LAPACK is a software package provided by Univ. of Tennessee, --
113* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
114*
115* .. Scalar Arguments ..
116 INTEGER INFO, N
117* ..
118* .. Array Arguments ..
119 DOUBLE PRECISION Z( * )
120* ..
121*
122* =====================================================================
123*
124* .. Parameters ..
125 DOUBLE PRECISION CBIAS
126 parameter( cbias = 1.50d0 )
127 DOUBLE PRECISION ZERO, HALF, ONE, TWO, FOUR, HUNDRD
128 parameter( zero = 0.0d0, half = 0.5d0, one = 1.0d0,
129 $ two = 2.0d0, four = 4.0d0, hundrd = 100.0d0 )
130* ..
131* .. Local Scalars ..
132 LOGICAL IEEE
133 INTEGER I0, I1, I4, IINFO, IPN4, ITER, IWHILA, IWHILB,
134 $ K, KMIN, N0, N1, NBIG, NDIV, NFAIL, PP, SPLT,
135 $ TTYPE
136 DOUBLE PRECISION D, DEE, DEEMIN, DESIG, DMIN, DMIN1, DMIN2, DN,
137 $ DN1, DN2, E, EMAX, EMIN, EPS, G, OLDEMN, QMAX,
138 $ QMIN, S, SAFMIN, SIGMA, T, TAU, TEMP, TOL,
139 $ TOL2, TRACE, ZMAX, TEMPE, TEMPQ
140* ..
141* .. External Subroutines ..
142 EXTERNAL dlasq3, dlasrt, xerbla
143* ..
144* .. External Functions ..
145 INTEGER ILAENV
146 DOUBLE PRECISION DLAMCH
147 EXTERNAL dlamch, ilaenv
148* ..
149* .. Intrinsic Functions ..
150 INTRINSIC abs, dble, max, min, sqrt
151* ..
152* .. Executable Statements ..
153*
154* Test the input arguments.
155* (in case DLASQ2 is not called by DLASQ1)
156*
157 info = 0
158 eps = dlamch( 'Precision' )
159 safmin = dlamch( 'Safe minimum' )
160 tol = eps*hundrd
161 tol2 = tol**2
162*
163 IF( n.LT.0 ) THEN
164 info = -1
165 CALL xerbla( 'DLASQ2', 1 )
166 RETURN
167 ELSE IF( n.EQ.0 ) THEN
168 RETURN
169 ELSE IF( n.EQ.1 ) THEN
170*
171* 1-by-1 case.
172*
173 IF( z( 1 ).LT.zero ) THEN
174 info = -201
175 CALL xerbla( 'DLASQ2', 2 )
176 END IF
177 RETURN
178 ELSE IF( n.EQ.2 ) THEN
179*
180* 2-by-2 case.
181*
182 IF( z( 1 ).LT.zero ) THEN
183 info = -201
184 CALL xerbla( 'DLASQ2', 2 )
185 RETURN
186 ELSE IF( z( 2 ).LT.zero ) THEN
187 info = -202
188 CALL xerbla( 'DLASQ2', 2 )
189 RETURN
190 ELSE IF( z( 3 ).LT.zero ) THEN
191 info = -203
192 CALL xerbla( 'DLASQ2', 2 )
193 RETURN
194 ELSE IF( z( 3 ).GT.z( 1 ) ) THEN
195 d = z( 3 )
196 z( 3 ) = z( 1 )
197 z( 1 ) = d
198 END IF
199 z( 5 ) = z( 1 ) + z( 2 ) + z( 3 )
200 IF( z( 2 ).GT.z( 3 )*tol2 ) THEN
201 t = half*( ( z( 1 )-z( 3 ) )+z( 2 ) )
202 s = z( 3 )*( z( 2 ) / t )
203 IF( s.LE.t ) THEN
204 s = z( 3 )*( z( 2 ) / ( t*( one+sqrt( one+s / t ) ) ) )
205 ELSE
206 s = z( 3 )*( z( 2 ) / ( t+sqrt( t )*sqrt( t+s ) ) )
207 END IF
208 t = z( 1 ) + ( s+z( 2 ) )
209 z( 3 ) = z( 3 )*( z( 1 ) / t )
210 z( 1 ) = t
211 END IF
212 z( 2 ) = z( 3 )
213 z( 6 ) = z( 2 ) + z( 1 )
214 RETURN
215 END IF
216*
217* Check for negative data and compute sums of q's and e's.
218*
219 z( 2*n ) = zero
220 emin = z( 2 )
221 qmax = zero
222 zmax = zero
223 d = zero
224 e = zero
225*
226 DO 10 k = 1, 2*( n-1 ), 2
227 IF( z( k ).LT.zero ) THEN
228 info = -( 200+k )
229 CALL xerbla( 'DLASQ2', 2 )
230 RETURN
231 ELSE IF( z( k+1 ).LT.zero ) THEN
232 info = -( 200+k+1 )
233 CALL xerbla( 'DLASQ2', 2 )
234 RETURN
235 END IF
236 d = d + z( k )
237 e = e + z( k+1 )
238 qmax = max( qmax, z( k ) )
239 emin = min( emin, z( k+1 ) )
240 zmax = max( qmax, zmax, z( k+1 ) )
241 10 CONTINUE
242 IF( z( 2*n-1 ).LT.zero ) THEN
243 info = -( 200+2*n-1 )
244 CALL xerbla( 'DLASQ2', 2 )
245 RETURN
246 END IF
247 d = d + z( 2*n-1 )
248 qmax = max( qmax, z( 2*n-1 ) )
249 zmax = max( qmax, zmax )
250*
251* Check for diagonality.
252*
253 IF( e.EQ.zero ) THEN
254 DO 20 k = 2, n
255 z( k ) = z( 2*k-1 )
256 20 CONTINUE
257 CALL dlasrt( 'D', n, z, iinfo )
258 z( 2*n-1 ) = d
259 RETURN
260 END IF
261*
262 trace = d + e
263*
264* Check for zero data.
265*
266 IF( trace.EQ.zero ) THEN
267 z( 2*n-1 ) = zero
268 RETURN
269 END IF
270*
271* Check whether the machine is IEEE conformable.
272*
273 ieee = ( ilaenv( 10, 'DLASQ2', 'N', 1, 2, 3, 4 ).EQ.1 )
274*
275* Rearrange data for locality: Z=(q1,qq1,e1,ee1,q2,qq2,e2,ee2,...).
276*
277 DO 30 k = 2*n, 2, -2
278 z( 2*k ) = zero
279 z( 2*k-1 ) = z( k )
280 z( 2*k-2 ) = zero
281 z( 2*k-3 ) = z( k-1 )
282 30 CONTINUE
283*
284 i0 = 1
285 n0 = n
286*
287* Reverse the qd-array, if warranted.
288*
289 IF( cbias*z( 4*i0-3 ).LT.z( 4*n0-3 ) ) THEN
290 ipn4 = 4*( i0+n0 )
291 DO 40 i4 = 4*i0, 2*( i0+n0-1 ), 4
292 temp = z( i4-3 )
293 z( i4-3 ) = z( ipn4-i4-3 )
294 z( ipn4-i4-3 ) = temp
295 temp = z( i4-1 )
296 z( i4-1 ) = z( ipn4-i4-5 )
297 z( ipn4-i4-5 ) = temp
298 40 CONTINUE
299 END IF
300*
301* Initial split checking via dqd and Li's test.
302*
303 pp = 0
304*
305 DO 80 k = 1, 2
306*
307 d = z( 4*n0+pp-3 )
308 DO 50 i4 = 4*( n0-1 ) + pp, 4*i0 + pp, -4
309 IF( z( i4-1 ).LE.tol2*d ) THEN
310 z( i4-1 ) = -zero
311 d = z( i4-3 )
312 ELSE
313 d = z( i4-3 )*( d / ( d+z( i4-1 ) ) )
314 END IF
315 50 CONTINUE
316*
317* dqd maps Z to ZZ plus Li's test.
318*
319 emin = z( 4*i0+pp+1 )
320 d = z( 4*i0+pp-3 )
321 DO 60 i4 = 4*i0 + pp, 4*( n0-1 ) + pp, 4
322 z( i4-2*pp-2 ) = d + z( i4-1 )
323 IF( z( i4-1 ).LE.tol2*d ) THEN
324 z( i4-1 ) = -zero
325 z( i4-2*pp-2 ) = d
326 z( i4-2*pp ) = zero
327 d = z( i4+1 )
328 ELSE IF( safmin*z( i4+1 ).LT.z( i4-2*pp-2 ) .AND.
329 $ safmin*z( i4-2*pp-2 ).LT.z( i4+1 ) ) THEN
330 temp = z( i4+1 ) / z( i4-2*pp-2 )
331 z( i4-2*pp ) = z( i4-1 )*temp
332 d = d*temp
333 ELSE
334 z( i4-2*pp ) = z( i4+1 )*( z( i4-1 ) / z( i4-2*pp-2 ) )
335 d = z( i4+1 )*( d / z( i4-2*pp-2 ) )
336 END IF
337 emin = min( emin, z( i4-2*pp ) )
338 60 CONTINUE
339 z( 4*n0-pp-2 ) = d
340*
341* Now find qmax.
342*
343 qmax = z( 4*i0-pp-2 )
344 DO 70 i4 = 4*i0 - pp + 2, 4*n0 - pp - 2, 4
345 qmax = max( qmax, z( i4 ) )
346 70 CONTINUE
347*
348* Prepare for the next iteration on K.
349*
350 pp = 1 - pp
351 80 CONTINUE
352*
353* Initialise variables to pass to DLASQ3.
354*
355 ttype = 0
356 dmin1 = zero
357 dmin2 = zero
358 dn = zero
359 dn1 = zero
360 dn2 = zero
361 g = zero
362 tau = zero
363*
364 iter = 2
365 nfail = 0
366 ndiv = 2*( n0-i0 )
367*
368 DO 160 iwhila = 1, n + 1
369 IF( n0.LT.1 )
370 $ GO TO 170
371*
372* While array unfinished do
373*
374* E(N0) holds the value of SIGMA when submatrix in I0:N0
375* splits from the rest of the array, but is negated.
376*
377 desig = zero
378 IF( n0.EQ.n ) THEN
379 sigma = zero
380 ELSE
381 sigma = -z( 4*n0-1 )
382 END IF
383 IF( sigma.LT.zero ) THEN
384 info = 1
385 RETURN
386 END IF
387*
388* Find last unreduced submatrix's top index I0, find QMAX and
389* EMIN. Find Gershgorin-type bound if Q's much greater than E's.
390*
391 emax = zero
392 IF( n0.GT.i0 ) THEN
393 emin = abs( z( 4*n0-5 ) )
394 ELSE
395 emin = zero
396 END IF
397 qmin = z( 4*n0-3 )
398 qmax = qmin
399 DO 90 i4 = 4*n0, 8, -4
400 IF( z( i4-5 ).LE.zero )
401 $ GO TO 100
402 IF( qmin.GE.four*emax ) THEN
403 qmin = min( qmin, z( i4-3 ) )
404 emax = max( emax, z( i4-5 ) )
405 END IF
406 qmax = max( qmax, z( i4-7 )+z( i4-5 ) )
407 emin = min( emin, z( i4-5 ) )
408 90 CONTINUE
409 i4 = 4
410*
411 100 CONTINUE
412 i0 = i4 / 4
413 pp = 0
414*
415 IF( n0-i0.GT.1 ) THEN
416 dee = z( 4*i0-3 )
417 deemin = dee
418 kmin = i0
419 DO 110 i4 = 4*i0+1, 4*n0-3, 4
420 dee = z( i4 )*( dee /( dee+z( i4-2 ) ) )
421 IF( dee.LE.deemin ) THEN
422 deemin = dee
423 kmin = ( i4+3 )/4
424 END IF
425 110 CONTINUE
426 IF( (kmin-i0)*2.LT.n0-kmin .AND.
427 $ deemin.LE.half*z(4*n0-3) ) THEN
428 ipn4 = 4*( i0+n0 )
429 pp = 2
430 DO 120 i4 = 4*i0, 2*( i0+n0-1 ), 4
431 temp = z( i4-3 )
432 z( i4-3 ) = z( ipn4-i4-3 )
433 z( ipn4-i4-3 ) = temp
434 temp = z( i4-2 )
435 z( i4-2 ) = z( ipn4-i4-2 )
436 z( ipn4-i4-2 ) = temp
437 temp = z( i4-1 )
438 z( i4-1 ) = z( ipn4-i4-5 )
439 z( ipn4-i4-5 ) = temp
440 temp = z( i4 )
441 z( i4 ) = z( ipn4-i4-4 )
442 z( ipn4-i4-4 ) = temp
443 120 CONTINUE
444 END IF
445 END IF
446*
447* Put -(initial shift) into DMIN.
448*
449 dmin = -max( zero, qmin-two*sqrt( qmin )*sqrt( emax ) )
450*
451* Now I0:N0 is unreduced.
452* PP = 0 for ping, PP = 1 for pong.
453* PP = 2 indicates that flipping was applied to the Z array and
454* and that the tests for deflation upon entry in DLASQ3
455* should not be performed.
456*
457 nbig = 100*( n0-i0+1 )
458 DO 140 iwhilb = 1, nbig
459 IF( i0.GT.n0 )
460 $ GO TO 150
461*
462* While submatrix unfinished take a good dqds step.
463*
464 CALL dlasq3( i0, n0, z, pp, dmin, sigma, desig, qmax,
465 $ nfail,
466 $ iter, ndiv, ieee, ttype, dmin1, dmin2, dn, dn1,
467 $ dn2, g, tau )
468*
469 pp = 1 - pp
470*
471* When EMIN is very small check for splits.
472*
473 IF( pp.EQ.0 .AND. n0-i0.GE.3 ) THEN
474 IF( z( 4*n0 ).LE.tol2*qmax .OR.
475 $ z( 4*n0-1 ).LE.tol2*sigma ) THEN
476 splt = i0 - 1
477 qmax = z( 4*i0-3 )
478 emin = z( 4*i0-1 )
479 oldemn = z( 4*i0 )
480 DO 130 i4 = 4*i0, 4*( n0-3 ), 4
481 IF( z( i4 ).LE.tol2*z( i4-3 ) .OR.
482 $ z( i4-1 ).LE.tol2*sigma ) THEN
483 z( i4-1 ) = -sigma
484 splt = i4 / 4
485 qmax = zero
486 emin = z( i4+3 )
487 oldemn = z( i4+4 )
488 ELSE
489 qmax = max( qmax, z( i4+1 ) )
490 emin = min( emin, z( i4-1 ) )
491 oldemn = min( oldemn, z( i4 ) )
492 END IF
493 130 CONTINUE
494 z( 4*n0-1 ) = emin
495 z( 4*n0 ) = oldemn
496 i0 = splt + 1
497 END IF
498 END IF
499*
500 140 CONTINUE
501*
502 info = 2
503*
504* Maximum number of iterations exceeded, restore the shift
505* SIGMA and place the new d's and e's in a qd array.
506* This might need to be done for several blocks
507*
508 i1 = i0
509 n1 = n0
510 145 CONTINUE
511 tempq = z( 4*i0-3 )
512 z( 4*i0-3 ) = z( 4*i0-3 ) + sigma
513 DO k = i0+1, n0
514 tempe = z( 4*k-5 )
515 z( 4*k-5 ) = z( 4*k-5 ) * (tempq / z( 4*k-7 ))
516 tempq = z( 4*k-3 )
517 z( 4*k-3 ) = z( 4*k-3 ) + sigma + tempe - z( 4*k-5 )
518 END DO
519*
520* Prepare to do this on the previous block if there is one
521*
522 IF( i1.GT.1 ) THEN
523 n1 = i1-1
524 DO WHILE( ( i1.GE.2 ) .AND. ( z(4*i1-5).GE.zero ) )
525 i1 = i1 - 1
526 END DO
527 sigma = -z(4*n1-1)
528 GO TO 145
529 END IF
530
531 DO k = 1, n
532 z( 2*k-1 ) = z( 4*k-3 )
533*
534* Only the block 1..N0 is unfinished. The rest of the e's
535* must be essentially zero, although sometimes other data
536* has been stored in them.
537*
538 IF( k.LT.n0 ) THEN
539 z( 2*k ) = z( 4*k-1 )
540 ELSE
541 z( 2*k ) = 0
542 END IF
543 END DO
544 RETURN
545*
546* end IWHILB
547*
548 150 CONTINUE
549*
550 160 CONTINUE
551*
552 info = 3
553 RETURN
554*
555* end IWHILA
556*
557 170 CONTINUE
558*
559* Move q's to the front.
560*
561 DO 180 k = 2, n
562 z( k ) = z( 4*k-3 )
563 180 CONTINUE
564*
565* Sort and compute sum of eigenvalues.
566*
567 CALL dlasrt( 'D', n, z, iinfo )
568*
569 e = zero
570 DO 190 k = n, 1, -1
571 e = e + z( k )
572 190 CONTINUE
573*
574* Store trace, sum(eigenvalues) and information on performance.
575*
576 z( 2*n+1 ) = trace
577 z( 2*n+2 ) = e
578 z( 2*n+3 ) = dble( iter )
579 z( 2*n+4 ) = dble( ndiv ) / dble( n**2 )
580 z( 2*n+5 ) = hundrd*nfail / dble( iter )
581 RETURN
582*
583* End of DLASQ2
584*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:160
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
subroutine dlasq3(i0, n0, z, pp, dmin, sigma, desig, qmax, nfail, iter, ndiv, ieee, ttype, dmin1, dmin2, dn, dn1, dn2, g, tau)
DLASQ3 checks for deflation, computes a shift and calls dqds. Used by sbdsqr.
Definition dlasq3.f:181
subroutine dlasrt(id, n, d, info)
DLASRT sorts numbers in increasing or decreasing order.
Definition dlasrt.f:86
Here is the call graph for this function:
Here is the caller graph for this function: