imtql1.f 4.7 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151
  1. *DECK IMTQL1
  2. SUBROUTINE IMTQL1 (N, D, E, IERR)
  3. C***BEGIN PROLOGUE IMTQL1
  4. C***PURPOSE Compute the eigenvalues of a symmetric tridiagonal matrix
  5. C using the implicit QL method.
  6. C***LIBRARY SLATEC (EISPACK)
  7. C***CATEGORY D4A5, D4C2A
  8. C***TYPE SINGLE PRECISION (IMTQL1-S)
  9. C***KEYWORDS EIGENVALUES, EIGENVECTORS, EISPACK
  10. C***AUTHOR Smith, B. T., et al.
  11. C***DESCRIPTION
  12. C
  13. C This subroutine is a translation of the ALGOL procedure IMTQL1,
  14. C NUM. MATH. 12, 377-383(1968) by Martin and Wilkinson,
  15. C as modified in NUM. MATH. 15, 450(1970) by Dubrulle.
  16. C HANDBOOK FOR AUTO. COMP., VOL.II-LINEAR ALGEBRA, 241-248(1971).
  17. C
  18. C This subroutine finds the eigenvalues of a SYMMETRIC
  19. C TRIDIAGONAL matrix by the implicit QL method.
  20. C
  21. C On INPUT
  22. C
  23. C N is the order of the matrix. N is an INTEGER variable.
  24. C
  25. C D contains the diagonal elements of the symmetric tridiagonal
  26. C matrix. D is a one-dimensional REAL array, dimensioned D(N).
  27. C
  28. C E contains the subdiagonal elements of the symmetric
  29. C tridiagonal matrix in its last N-1 positions. E(1) is
  30. C arbitrary. E is a one-dimensional REAL array, dimensioned
  31. C E(N).
  32. C
  33. C On OUTPUT
  34. C
  35. C D contains the eigenvalues in ascending order. If an error
  36. C exit is made, the eigenvalues are correct and ordered for
  37. C indices 1, 2, ..., IERR-1, but may not be the smallest
  38. C eigenvalues.
  39. C
  40. C E has been destroyed.
  41. C
  42. C IERR is an INTEGER flag set to
  43. C Zero for normal return,
  44. C J if the J-th eigenvalue has not been
  45. C determined after 30 iterations.
  46. C The eigenvalues should be correct for indices
  47. C 1, 2, ..., IERR-1. These eigenvalues are
  48. C ordered, but are not necessarily the smallest.
  49. C
  50. C Calls PYTHAG(A,B) for sqrt(A**2 + B**2).
  51. C
  52. C Questions and comments should be directed to B. S. Garbow,
  53. C APPLIED MATHEMATICS DIVISION, ARGONNE NATIONAL LABORATORY
  54. C ------------------------------------------------------------------
  55. C
  56. C***REFERENCES B. T. Smith, J. M. Boyle, J. J. Dongarra, B. S. Garbow,
  57. C Y. Ikebe, V. C. Klema and C. B. Moler, Matrix Eigen-
  58. C system Routines - EISPACK Guide, Springer-Verlag,
  59. C 1976.
  60. C***ROUTINES CALLED PYTHAG
  61. C***REVISION HISTORY (YYMMDD)
  62. C 760101 DATE WRITTEN
  63. C 890831 Modified array declarations. (WRB)
  64. C 890831 REVISION DATE from Version 3.2
  65. C 891214 Prologue converted to Version 4.0 format. (BAB)
  66. C 920501 Reformatted the REFERENCES section. (WRB)
  67. C***END PROLOGUE IMTQL1
  68. C
  69. INTEGER I,J,L,M,N,II,MML,IERR
  70. REAL D(*),E(*)
  71. REAL B,C,F,G,P,R,S,S1,S2
  72. REAL PYTHAG
  73. C
  74. C***FIRST EXECUTABLE STATEMENT IMTQL1
  75. IERR = 0
  76. IF (N .EQ. 1) GO TO 1001
  77. C
  78. DO 100 I = 2, N
  79. 100 E(I-1) = E(I)
  80. C
  81. E(N) = 0.0E0
  82. C
  83. DO 290 L = 1, N
  84. J = 0
  85. C .......... LOOK FOR SMALL SUB-DIAGONAL ELEMENT ..........
  86. 105 DO 110 M = L, N
  87. IF (M .EQ. N) GO TO 120
  88. S1 = ABS(D(M)) + ABS(D(M+1))
  89. S2 = S1 + ABS(E(M))
  90. IF (S2 .EQ. S1) GO TO 120
  91. 110 CONTINUE
  92. C
  93. 120 P = D(L)
  94. IF (M .EQ. L) GO TO 215
  95. IF (J .EQ. 30) GO TO 1000
  96. J = J + 1
  97. C .......... FORM SHIFT ..........
  98. G = (D(L+1) - P) / (2.0E0 * E(L))
  99. R = PYTHAG(G,1.0E0)
  100. G = D(M) - P + E(L) / (G + SIGN(R,G))
  101. S = 1.0E0
  102. C = 1.0E0
  103. P = 0.0E0
  104. MML = M - L
  105. C .......... FOR I=M-1 STEP -1 UNTIL L DO -- ..........
  106. DO 200 II = 1, MML
  107. I = M - II
  108. F = S * E(I)
  109. B = C * E(I)
  110. IF (ABS(F) .LT. ABS(G)) GO TO 150
  111. C = G / F
  112. R = SQRT(C*C+1.0E0)
  113. E(I+1) = F * R
  114. S = 1.0E0 / R
  115. C = C * S
  116. GO TO 160
  117. 150 S = F / G
  118. R = SQRT(S*S+1.0E0)
  119. E(I+1) = G * R
  120. C = 1.0E0 / R
  121. S = S * C
  122. 160 G = D(I+1) - P
  123. R = (D(I) - G) * S + 2.0E0 * C * B
  124. P = S * R
  125. D(I+1) = G + P
  126. G = C * R - B
  127. 200 CONTINUE
  128. C
  129. D(L) = D(L) - P
  130. E(L) = G
  131. E(M) = 0.0E0
  132. GO TO 105
  133. C .......... ORDER EIGENVALUES ..........
  134. 215 IF (L .EQ. 1) GO TO 250
  135. C .......... FOR I=L STEP -1 UNTIL 2 DO -- ..........
  136. DO 230 II = 2, L
  137. I = L + 2 - II
  138. IF (P .GE. D(I-1)) GO TO 270
  139. D(I) = D(I-1)
  140. 230 CONTINUE
  141. C
  142. 250 I = 1
  143. 270 D(I) = P
  144. 290 CONTINUE
  145. C
  146. GO TO 1001
  147. C .......... SET ERROR -- NO CONVERGENCE TO AN
  148. C EIGENVALUE AFTER 30 ITERATIONS ..........
  149. 1000 IERR = L
  150. 1001 RETURN
  151. END