| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203 | *DECK TQL2      SUBROUTINE TQL2 (NM, N, D, E, Z, IERR)C***BEGIN PROLOGUE  TQL2C***PURPOSE  Compute the eigenvalues and eigenvectors of symmetricC            tridiagonal matrix.C***LIBRARY   SLATEC (EISPACK)C***CATEGORY  D4A5, D4C2AC***TYPE      SINGLE PRECISION (TQL2-S)C***KEYWORDS  EIGENVALUES, EIGENVECTORS, EISPACKC***AUTHOR  Smith, B. T., et al.C***DESCRIPTIONCC     This subroutine is a translation of the ALGOL procedure TQL2,C     NUM. MATH. 11, 293-306(1968) by Bowdler, Martin, Reinsch, andC     Wilkinson.C     HANDBOOK FOR AUTO. COMP., VOL.II-LINEAR ALGEBRA, 227-240(1971).CC     This subroutine finds the eigenvalues and eigenvectorsC     of a SYMMETRIC TRIDIAGONAL matrix by the QL method.C     The eigenvectors of a FULL SYMMETRIC matrix can alsoC     be found if  TRED2  has been used to reduce thisC     full matrix to tridiagonal form.CC     On InputCC        NM must be set to the row dimension of the two-dimensionalC          array parameter, Z, as declared in the calling programC          dimension statement.  NM is an INTEGER variable.CC        N is the order of the matrix.  N is an INTEGER variable.C          N must be less than or equal to NM.CC        D contains the diagonal elements of the symmetric tridiagonalC          matrix.  D is a one-dimensional REAL array, dimensioned D(N).CC        E contains the subdiagonal elements of the symmetricC          tridiagonal matrix in its last N-1 positions.  E(1) isC          arbitrary.  E is a one-dimensional REAL array, dimensionedC          E(N).CC        Z contains the transformation matrix produced in theC          reduction by  TRED2, if performed.  If the eigenvectorsC          of the tridiagonal matrix are desired, Z must containC          the identity matrix.  Z is a two-dimensional REAL array,C          dimensioned Z(NM,N).CC      On OutputCC        D contains the eigenvalues in ascending order.  If anC          error exit is made, the eigenvalues are correct butC          unordered for indices 1, 2, ..., IERR-1.CC        E has been destroyed.CC        Z contains orthonormal eigenvectors of the symmetricC          tridiagonal (or full) matrix.  If an error exit is made,C          Z contains the eigenvectors associated with the storedC          eigenvalues.CC        IERR is an INTEGER flag set toC          Zero       for normal return,C          J          if the J-th eigenvalue has not beenC                     determined after 30 iterations.CC     Calls PYTHAG(A,B) for sqrt(A**2 + B**2).CC     Questions and comments should be directed to B. S. Garbow,C     APPLIED MATHEMATICS DIVISION, ARGONNE NATIONAL LABORATORYC     ------------------------------------------------------------------CC***REFERENCES  B. T. Smith, J. M. Boyle, J. J. Dongarra, B. S. Garbow,C                 Y. Ikebe, V. C. Klema and C. B. Moler, Matrix Eigen-C                 system Routines - EISPACK Guide, Springer-Verlag,C                 1976.C***ROUTINES CALLED  PYTHAGC***REVISION HISTORY  (YYMMDD)C   760101  DATE WRITTENC   890831  Modified array declarations.  (WRB)C   890831  REVISION DATE from Version 3.2C   891214  Prologue converted to Version 4.0 format.  (BAB)C   920501  Reformatted the REFERENCES section.  (WRB)C***END PROLOGUE  TQL2C      INTEGER I,J,K,L,M,N,II,L1,L2,NM,MML,IERR      REAL D(*),E(*),Z(NM,*)      REAL B,C,C2,C3,DL1,EL1,F,G,H,P,R,S,S2      REAL PYTHAGCC***FIRST EXECUTABLE STATEMENT  TQL2      IERR = 0      IF (N .EQ. 1) GO TO 1001C      DO 100 I = 2, N  100 E(I-1) = E(I)C      F = 0.0E0      B = 0.0E0      E(N) = 0.0E0C      DO 240 L = 1, N         J = 0         H = ABS(D(L)) + ABS(E(L))         IF (B .LT. H) B = HC     .......... LOOK FOR SMALL SUB-DIAGONAL ELEMENT ..........         DO 110 M = L, N            IF (B + ABS(E(M)) .EQ. B) GO TO 120C     .......... E(N) IS ALWAYS ZERO, SO THERE IS NO EXITC                THROUGH THE BOTTOM OF THE LOOP ..........  110    CONTINUEC  120    IF (M .EQ. L) GO TO 220  130    IF (J .EQ. 30) GO TO 1000         J = J + 1C     .......... FORM SHIFT ..........         L1 = L + 1         L2 = L1 + 1         G = D(L)         P = (D(L1) - G) / (2.0E0 * E(L))         R = PYTHAG(P,1.0E0)         D(L) = E(L) / (P + SIGN(R,P))         D(L1) = E(L) * (P + SIGN(R,P))         DL1 = D(L1)         H = G - D(L)         IF (L2 .GT. N) GO TO 145C         DO 140 I = L2, N  140    D(I) = D(I) - HC  145    F = F + HC     .......... QL TRANSFORMATION ..........         P = D(M)         C = 1.0E0         C2 = C         EL1 = E(L1)         S = 0.0E0         MML = M - LC     .......... FOR I=M-1 STEP -1 UNTIL L DO -- ..........         DO 200 II = 1, MML            C3 = C2            C2 = C            S2 = S            I = M - II            G = C * E(I)            H = C * P            IF (ABS(P) .LT. ABS(E(I))) GO TO 150            C = E(I) / P            R = SQRT(C*C+1.0E0)            E(I+1) = S * P * R            S = C / R            C = 1.0E0 / R            GO TO 160  150       C = P / E(I)            R = SQRT(C*C+1.0E0)            E(I+1) = S * E(I) * R            S = 1.0E0 / R            C = C * S  160       P = C * D(I) - S * G            D(I+1) = H + S * (C * G + S * D(I))C     .......... FORM VECTOR ..........            DO 180 K = 1, N               H = Z(K,I+1)               Z(K,I+1) = S * Z(K,I) + C * H               Z(K,I) = C * Z(K,I) - S * H  180       CONTINUEC  200    CONTINUEC         P = -S * S2 * C3 * EL1 * E(L) / DL1         E(L) = S * P         D(L) = C * P         IF (B + ABS(E(L)) .GT. B) GO TO 130  220    D(L) = D(L) + F  240 CONTINUEC     .......... ORDER EIGENVALUES AND EIGENVECTORS ..........      DO 300 II = 2, N         I = II - 1         K = I         P = D(I)C         DO 260 J = II, N            IF (D(J) .GE. P) GO TO 260            K = J            P = D(J)  260    CONTINUEC         IF (K .EQ. I) GO TO 300         D(K) = D(I)         D(I) = PC         DO 280 J = 1, N            P = Z(J,I)            Z(J,I) = Z(J,K)            Z(J,K) = P  280    CONTINUEC  300 CONTINUEC      GO TO 1001C     .......... SET ERROR -- NO CONVERGENCE TO ANC                EIGENVALUE AFTER 30 ITERATIONS .......... 1000 IERR = L 1001 RETURN      END
 |