imtqlv.f 6.2 KB

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