284
285
286
287
288
289
290 INTEGER DOL, DOU, INFO, LDZ, M, N
291 REAL MINRGP, PIVMIN, RTOL1, RTOL2, VL, VU
292
293
294 INTEGER IBLOCK( * ), INDEXW( * ), ISPLIT( * ),
295 $ ISUPPZ( * ), IWORK( * )
296 REAL D( * ), GERS( * ), L( * ), W( * ), WERR( * ),
297 $ WGAP( * ), WORK( * )
298 COMPLEX Z( LDZ, * )
299
300
301
302
303
304 INTEGER MAXITR
305 parameter( maxitr = 10 )
306 COMPLEX CZERO
307 parameter( czero = ( 0.0e0, 0.0e0 ) )
308 REAL ZERO, ONE, TWO, THREE, FOUR, HALF
309 parameter( zero = 0.0e0, one = 1.0e0,
310 $ two = 2.0e0, three = 3.0e0,
311 $ four = 4.0e0, half = 0.5e0)
312
313
314 LOGICAL ESKIP, NEEDBS, STP2II, TRYRQC, USEDBS, USEDRQ
315 INTEGER DONE, I, IBEGIN, IDONE, IEND, II, IINDC1,
316 $ IINDC2, IINDR, IINDWK, IINFO, IM, IN, INDEIG,
317 $ INDLD, INDLLD, INDWRK, ISUPMN, ISUPMX, ITER,
318 $ ITMP1, J, JBLK, K, MINIWSIZE, MINWSIZE, NCLUS,
319 $ NDEPTH, NEGCNT, NEWCLS, NEWFST, NEWFTT, NEWLST,
320 $ NEWSIZ, OFFSET, OLDCLS, OLDFST, OLDIEN, OLDLST,
321 $ OLDNCL, P, PARITY, Q, WBEGIN, WEND, WINDEX,
322 $ WINDMN, WINDPL, ZFROM, ZTO, ZUSEDL, ZUSEDU,
323 $ ZUSEDW
324 INTEGER INDIN1, INDIN2
325 REAL BSTRES, BSTW, EPS, FUDGE, GAP, GAPTOL, GL, GU,
326 $ LAMBDA, LEFT, LGAP, MINGMA, NRMINV, RESID,
327 $ RGAP, RIGHT, RQCORR, RQTOL, SAVGAP, SGNDEF,
328 $ SIGMA, SPDIAM, SSIGMA, TAU, TMP, TOL, ZTZ
329
330
331 REAL SLAMCH
333
334
338
339
340 INTRINSIC abs, real, max, min
341 INTRINSIC cmplx
342
343
344
345
346 info = 0
347
348
349
350 IF( (n.LE.0).OR.(m.LE.0) ) THEN
351 RETURN
352 END IF
353
354
355 indld = n+1
356 indlld= 2*n+1
357 indin1 = 3*n + 1
358 indin2 = 4*n + 1
359 indwrk = 5*n + 1
360 minwsize = 12 * n
361
362 DO 5 i= 1,minwsize
363 work( i ) = zero
364 5 CONTINUE
365
366
367
368 iindr = 0
369
370
371 iindc1 = n
372 iindc2 = 2*n
373 iindwk = 3*n + 1
374
375 miniwsize = 7 * n
376 DO 10 i= 1,miniwsize
377 iwork( i ) = 0
378 10 CONTINUE
379
380 zusedl = 1
381 IF(dol.GT.1) THEN
382
383 zusedl = dol-1
384 ENDIF
385 zusedu = m
386 IF(dou.LT.m) THEN
387
388 zusedu = dou+1
389 ENDIF
390
391 zusedw = zusedu - zusedl + 1
392
393
394 CALL claset(
'Full', n, zusedw, czero, czero,
395 $ z(1,zusedl), ldz )
396
397 eps =
slamch(
'Precision' )
398 rqtol = two * eps
399
400
401 tryrqc = .true.
402
403 IF((dol.EQ.1).AND.(dou.EQ.m)) THEN
404 ELSE
405
406
407
408 rtol1 = four * eps
409 rtol2 = four * eps
410 ENDIF
411
412
413
414
415
416
417
418
419 done = 0
420 ibegin = 1
421 wbegin = 1
422 DO 170 jblk = 1, iblock( m )
423 iend = isplit( jblk )
424 sigma = l( iend )
425
426
427 wend = wbegin - 1
428 15 CONTINUE
429 IF( wend.LT.m ) THEN
430 IF( iblock( wend+1 ).EQ.jblk ) THEN
431 wend = wend + 1
432 GO TO 15
433 END IF
434 END IF
435 IF( wend.LT.wbegin ) THEN
436 ibegin = iend + 1
437 GO TO 170
438 ELSEIF( (wend.LT.dol).OR.(wbegin.GT.dou) ) THEN
439 ibegin = iend + 1
440 wbegin = wend + 1
441 GO TO 170
442 END IF
443
444
445 gl = gers( 2*ibegin-1 )
446 gu = gers( 2*ibegin )
447 DO 20 i = ibegin+1 , iend
448 gl = min( gers( 2*i-1 ), gl )
449 gu = max( gers( 2*i ), gu )
450 20 CONTINUE
451 spdiam = gu - gl
452
453
454 oldien = ibegin - 1
455
456 in = iend - ibegin + 1
457
458 im = wend - wbegin + 1
459
460
461 IF( ibegin.EQ.iend ) THEN
462 done = done+1
463 z( ibegin, wbegin ) = cmplx( one, zero )
464 isuppz( 2*wbegin-1 ) = ibegin
465 isuppz( 2*wbegin ) = ibegin
466 w( wbegin ) = w( wbegin ) + sigma
467 work( wbegin ) = w( wbegin )
468 ibegin = iend + 1
469 wbegin = wbegin + 1
470 GO TO 170
471 END IF
472
473
474
475
476
477
478
479 CALL scopy( im, w( wbegin ), 1,
480 $ work( wbegin ), 1 )
481
482
483
484 DO 30 i=1,im
485 w(wbegin+i-1) = w(wbegin+i-1)+sigma
486 30 CONTINUE
487
488
489
490 ndepth = 0
491
492 parity = 1
493
494
495 nclus = 1
496 iwork( iindc1+1 ) = 1
497 iwork( iindc1+2 ) = im
498
499
500
501 idone = 0
502
503
504
505 40 CONTINUE
506 IF( idone.LT.im ) THEN
507
508 IF( ndepth.GT.m ) THEN
509 info = -2
510 RETURN
511 ENDIF
512
513
514 oldncl = nclus
515
516 nclus = 0
517
518 parity = 1 - parity
519 IF( parity.EQ.0 ) THEN
520 oldcls = iindc1
521 newcls = iindc2
522 ELSE
523 oldcls = iindc2
524 newcls = iindc1
525 END IF
526
527 DO 150 i = 1, oldncl
528 j = oldcls + 2*i
529
530
531
532 oldfst = iwork( j-1 )
533 oldlst = iwork( j )
534 IF( ndepth.GT.0 ) THEN
535
536
537
538
539
540 IF((dol.EQ.1).AND.(dou.EQ.m)) THEN
541
542
543 j = wbegin + oldfst - 1
544 ELSE
545 IF(wbegin+oldfst-1.LT.dol) THEN
546
547 j = dol - 1
548 ELSEIF(wbegin+oldfst-1.GT.dou) THEN
549
550 j = dou
551 ELSE
552 j = wbegin + oldfst - 1
553 ENDIF
554 ENDIF
555 DO 45 k = 1, in - 1
556 d( ibegin+k-1 ) = real( z( ibegin+k-1,
557 $ j ) )
558 l( ibegin+k-1 ) = real( z( ibegin+k-1,
559 $ j+1 ) )
560 45 CONTINUE
561 d( iend ) = real( z( iend, j ) )
562 sigma = real( z( iend, j+1 ) )
563
564
565 CALL claset(
'Full', in, 2, czero, czero,
566 $ z( ibegin, j), ldz )
567 END IF
568
569
570 DO 50 j = ibegin, iend-1
571 tmp = d( j )*l( j )
572 work( indld-1+j ) = tmp
573 work( indlld-1+j ) = tmp*l( j )
574 50 CONTINUE
575
576 IF( ndepth.GT.0 ) THEN
577
578
579 p = indexw( wbegin-1+oldfst )
580 q = indexw( wbegin-1+oldlst )
581
582
583
584 offset = indexw( wbegin ) - 1
585
586
587 CALL slarrb( in, d( ibegin ),
588 $ work(indlld+ibegin-1),
589 $ p, q, rtol1, rtol2, offset,
590 $ work(wbegin),wgap(wbegin),werr(wbegin),
591 $ work( indwrk ), iwork( iindwk ),
592 $ pivmin, spdiam, in, iinfo )
593 IF( iinfo.NE.0 ) THEN
594 info = -1
595 RETURN
596 ENDIF
597
598
599
600
601
602
603
604 IF( oldfst.GT.1) THEN
605 wgap( wbegin+oldfst-2 ) =
606 $ max(wgap(wbegin+oldfst-2),
607 $ w(wbegin+oldfst-1)-werr(wbegin+oldfst-1)
608 $ - w(wbegin+oldfst-2)-werr(wbegin+oldfst-2) )
609 ENDIF
610 IF( wbegin + oldlst -1 .LT. wend ) THEN
611 wgap( wbegin+oldlst-1 ) =
612 $ max(wgap(wbegin+oldlst-1),
613 $ w(wbegin+oldlst)-werr(wbegin+oldlst)
614 $ - w(wbegin+oldlst-1)-werr(wbegin+oldlst-1) )
615 ENDIF
616
617
618 DO 53 j=oldfst,oldlst
619 w(wbegin+j-1) = work(wbegin+j-1)+sigma
620 53 CONTINUE
621 END IF
622
623
624 newfst = oldfst
625 DO 140 j = oldfst, oldlst
626 IF( j.EQ.oldlst ) THEN
627
628
629 newlst = j
630 ELSE IF ( wgap( wbegin + j -1).GE.
631 $ minrgp* abs( work(wbegin + j -1) ) ) THEN
632
633
634 newlst = j
635 ELSE
636
637
638 GOTO 140
639 END IF
640
641
642 newsiz = newlst - newfst + 1
643
644
645
646 IF((dol.EQ.1).AND.(dou.EQ.m)) THEN
647
648
649 newftt = wbegin + newfst - 1
650 ELSE
651 IF(wbegin+newfst-1.LT.dol) THEN
652
653 newftt = dol - 1
654 ELSEIF(wbegin+newfst-1.GT.dou) THEN
655
656 newftt = dou
657 ELSE
658 newftt = wbegin + newfst - 1
659 ENDIF
660 ENDIF
661
662 IF( newsiz.GT.1) THEN
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677 IF( newfst.EQ.1 ) THEN
678 lgap = max( zero,
679 $ w(wbegin)-werr(wbegin) - vl )
680 ELSE
681 lgap = wgap( wbegin+newfst-2 )
682 ENDIF
683 rgap = wgap( wbegin+newlst-1 )
684
685
686
687
688
689
690 DO 55 k =1,2
691 IF(k.EQ.1) THEN
692 p = indexw( wbegin-1+newfst )
693 ELSE
694 p = indexw( wbegin-1+newlst )
695 ENDIF
696 offset = indexw( wbegin ) - 1
697 CALL slarrb( in, d(ibegin),
698 $ work( indlld+ibegin-1 ),p,p,
699 $ rqtol, rqtol, offset,
700 $ work(wbegin),wgap(wbegin),
701 $ werr(wbegin),work( indwrk ),
702 $ iwork( iindwk ), pivmin, spdiam,
703 $ in, iinfo )
704 55 CONTINUE
705
706 IF((wbegin+newlst-1.LT.dol).OR.
707 $ (wbegin+newfst-1.GT.dou)) THEN
708
709
710
711
712
713
714
715 idone = idone + newlst - newfst + 1
716 GOTO 139
717 ENDIF
718
719
720
721
722
723 CALL slarrf( in, d( ibegin ), l( ibegin ),
724 $ work(indld+ibegin-1),
725 $ newfst, newlst, work(wbegin),
726 $ wgap(wbegin), werr(wbegin),
727 $ spdiam, lgap, rgap, pivmin, tau,
728 $ work( indin1 ), work( indin2 ),
729 $ work( indwrk ), iinfo )
730
731
732
733 DO 56 k = 1, in-1
734 z( ibegin+k-1, newftt ) =
735 $ cmplx( work( indin1+k-1 ), zero )
736 z( ibegin+k-1, newftt+1 ) =
737 $ cmplx( work( indin2+k-1 ), zero )
738 56 CONTINUE
739 z( iend, newftt ) =
740 $ cmplx( work( indin1+in-1 ), zero )
741 IF( iinfo.EQ.0 ) THEN
742
743
744 ssigma = sigma + tau
745 z( iend, newftt+1 ) = cmplx( ssigma, zero )
746
747
748 DO 116 k = newfst, newlst
749 fudge =
750 $ three*eps*abs(work(wbegin+k-1))
751 work( wbegin + k - 1 ) =
752 $ work( wbegin + k - 1) - tau
753 fudge = fudge +
754 $ four*eps*abs(work(wbegin+k-1))
755
756 werr( wbegin + k - 1 ) =
757 $ werr( wbegin + k - 1 ) + fudge
758
759
760
761
762
763
764
765 116 CONTINUE
766
767 nclus = nclus + 1
768 k = newcls + 2*nclus
769 iwork( k-1 ) = newfst
770 iwork( k ) = newlst
771 ELSE
772 info = -2
773 RETURN
774 ENDIF
775 ELSE
776
777
778
779 iter = 0
780
781 tol = four * log(real(in)) * eps
782
783 k = newfst
784 windex = wbegin + k - 1
785 windmn = max(windex - 1,1)
786 windpl = min(windex + 1,m)
787 lambda = work( windex )
788 done = done + 1
789
790 IF((windex.LT.dol).OR.
791 $ (windex.GT.dou)) THEN
792 eskip = .true.
793 GOTO 125
794 ELSE
795 eskip = .false.
796 ENDIF
797 left = work( windex ) - werr( windex )
798 right = work( windex ) + werr( windex )
799 indeig = indexw( windex )
800
801
802
803
804
805
806
807 IF( k .EQ. 1) THEN
808
809
810
811
812
813
814 lgap = eps*max(abs(left),abs(right))
815 ELSE
816 lgap = wgap(windmn)
817 ENDIF
818 IF( k .EQ. im) THEN
819
820
821
822
823
824 rgap = eps*max(abs(left),abs(right))
825 ELSE
826 rgap = wgap(windex)
827 ENDIF
828 gap = min( lgap, rgap )
829 IF(( k .EQ. 1).OR.(k .EQ. im)) THEN
830
831
832
833 gaptol = zero
834 ELSE
835 gaptol = gap * eps
836 ENDIF
837 isupmn = in
838 isupmx = 1
839
840
841
842
843
844 savgap = wgap(windex)
845 wgap(windex) = gap
846
847
848
849
850
851
852 usedbs = .false.
853 usedrq = .false.
854
855 needbs = .NOT.tryrqc
856 120 CONTINUE
857
858 IF(needbs) THEN
859
860 usedbs = .true.
861 itmp1 = iwork( iindr+windex )
862 offset = indexw( wbegin ) - 1
863 CALL slarrb( in, d(ibegin),
864 $ work(indlld+ibegin-1),indeig,indeig,
865 $ zero, two*eps, offset,
866 $ work(wbegin),wgap(wbegin),
867 $ werr(wbegin),work( indwrk ),
868 $ iwork( iindwk ), pivmin, spdiam,
869 $ itmp1, iinfo )
870 IF( iinfo.NE.0 ) THEN
871 info = -3
872 RETURN
873 ENDIF
874 lambda = work( windex )
875
876
877 iwork( iindr+windex ) = 0
878 ENDIF
879
880 CALL clar1v( in, 1, in, lambda, d( ibegin ),
881 $ l( ibegin ), work(indld+ibegin-1),
882 $ work(indlld+ibegin-1),
883 $ pivmin, gaptol, z( ibegin, windex ),
884 $ .NOT.usedbs, negcnt, ztz, mingma,
885 $ iwork( iindr+windex ), isuppz( 2*windex-1 ),
886 $ nrminv, resid, rqcorr, work( indwrk ) )
887 IF(iter .EQ. 0) THEN
888 bstres = resid
889 bstw = lambda
890 ELSEIF(resid.LT.bstres) THEN
891 bstres = resid
892 bstw = lambda
893 ENDIF
894 isupmn = min(isupmn,isuppz( 2*windex-1 ))
895 isupmx = max(isupmx,isuppz( 2*windex ))
896 iter = iter + 1
897
898
899
900
901
902
903
904
905
906
907 IF( resid.GT.tol*gap .AND. abs( rqcorr ).GT.
908 $ rqtol*abs( lambda ) .AND. .NOT. usedbs)
909 $ THEN
910
911
912
913 IF(indeig.LE.negcnt) THEN
914
915 sgndef = -one
916 ELSE
917
918 sgndef = one
919 ENDIF
920
921
922 IF( ( rqcorr*sgndef.GE.zero )
923 $ .AND.( lambda + rqcorr.LE. right)
924 $ .AND.( lambda + rqcorr.GE. left)
925 $ ) THEN
926 usedrq = .true.
927
928 IF(sgndef.EQ.one) THEN
929
930
931 left = lambda
932
933
934
935
936
937
938 ELSE
939
940
941 right = lambda
942
943
944
945 ENDIF
946 work( windex ) =
947 $ half * (right + left)
948
949
950 lambda = lambda + rqcorr
951
952 werr( windex ) =
953 $ half * (right-left)
954 ELSE
955 needbs = .true.
956 ENDIF
957 IF(right-left.LT.rqtol*abs(lambda)) THEN
958
959
960 usedbs = .true.
961 GOTO 120
962 ELSEIF( iter.LT.maxitr ) THEN
963 GOTO 120
964 ELSEIF( iter.EQ.maxitr ) THEN
965 needbs = .true.
966 GOTO 120
967 ELSE
968 info = 5
969 RETURN
970 END IF
971 ELSE
972 stp2ii = .false.
973 IF(usedrq .AND. usedbs .AND.
974 $ bstres.LE.resid) THEN
975 lambda = bstw
976 stp2ii = .true.
977 ENDIF
978 IF (stp2ii) THEN
979
980 CALL clar1v( in, 1, in, lambda,
981 $ d( ibegin ), l( ibegin ),
982 $ work(indld+ibegin-1),
983 $ work(indlld+ibegin-1),
984 $ pivmin, gaptol, z( ibegin, windex ),
985 $ .NOT.usedbs, negcnt, ztz, mingma,
986 $ iwork( iindr+windex ),
987 $ isuppz( 2*windex-1 ),
988 $ nrminv, resid, rqcorr, work( indwrk ) )
989 ENDIF
990 work( windex ) = lambda
991 END IF
992
993
994
995 isuppz( 2*windex-1 ) = isuppz( 2*windex-1 )+oldien
996 isuppz( 2*windex ) = isuppz( 2*windex )+oldien
997 zfrom = isuppz( 2*windex-1 )
998 zto = isuppz( 2*windex )
999 isupmn = isupmn + oldien
1000 isupmx = isupmx + oldien
1001
1002 IF(isupmn.LT.zfrom) THEN
1003 DO 122 ii = isupmn,zfrom-1
1004 z( ii, windex ) = zero
1005 122 CONTINUE
1006 ENDIF
1007 IF(isupmx.GT.zto) THEN
1008 DO 123 ii = zto+1,isupmx
1009 z( ii, windex ) = zero
1010 123 CONTINUE
1011 ENDIF
1012 CALL csscal( zto-zfrom+1, nrminv,
1013 $ z( zfrom, windex ), 1 )
1014 125 CONTINUE
1015
1016 w( windex ) = lambda+sigma
1017
1018
1019
1020
1021
1022
1023 IF(.NOT.eskip) THEN
1024 IF( k.GT.1) THEN
1025 wgap( windmn ) = max( wgap(windmn),
1026 $ w(windex)-werr(windex)
1027 $ - w(windmn)-werr(windmn) )
1028 ENDIF
1029 IF( windex.LT.wend ) THEN
1030 wgap( windex ) = max( savgap,
1031 $ w( windpl )-werr( windpl )
1032 $ - w( windex )-werr( windex) )
1033 ENDIF
1034 ENDIF
1035 idone = idone + 1
1036 ENDIF
1037
1038
1039 139 CONTINUE
1040
1041 newfst = j + 1
1042 140 CONTINUE
1043 150 CONTINUE
1044 ndepth = ndepth + 1
1045 GO TO 40
1046 END IF
1047 ibegin = iend + 1
1048 wbegin = wend + 1
1049 170 CONTINUE
1050
1051
1052 RETURN
1053
1054
1055
subroutine scopy(n, sx, incx, sy, incy)
SCOPY
real function slamch(cmach)
SLAMCH
subroutine clar1v(n, b1, bn, lambda, d, l, ld, lld, pivmin, gaptol, z, wantnc, negcnt, ztz, mingma, r, isuppz, nrminv, resid, rqcorr, work)
CLAR1V computes the (scaled) r-th column of the inverse of the submatrix in rows b1 through bn of the...
subroutine slarrb(n, d, lld, ifirst, ilast, rtol1, rtol2, offset, w, wgap, werr, work, iwork, pivmin, spdiam, twist, info)
SLARRB provides limited bisection to locate eigenvalues for more accuracy.
subroutine slarrf(n, d, l, ld, clstrt, clend, w, wgap, werr, spdiam, clgapl, clgapr, pivmin, sigma, dplus, lplus, work, info)
SLARRF finds a new relatively robust representation such that at least one of the eigenvalues is rela...
subroutine claset(uplo, m, n, alpha, beta, a, lda)
CLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
subroutine csscal(n, sa, cx, incx)
CSSCAL