tinvit.f 9.6 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280
  1. *DECK TINVIT
  2. SUBROUTINE TINVIT (NM, N, D, E, E2, M, W, IND, Z, IERR, RV1, RV2,
  3. + RV3, RV4, RV6)
  4. C***BEGIN PROLOGUE TINVIT
  5. C***PURPOSE Compute the eigenvectors of symmetric tridiagonal matrix
  6. C corresponding to specified eigenvalues, using inverse
  7. C iteration.
  8. C***LIBRARY SLATEC (EISPACK)
  9. C***CATEGORY D4C3
  10. C***TYPE SINGLE PRECISION (TINVIT-S)
  11. C***KEYWORDS EIGENVECTORS, EISPACK
  12. C***AUTHOR Smith, B. T., et al.
  13. C***DESCRIPTION
  14. C
  15. C This subroutine is a translation of the inverse iteration tech-
  16. C nique in the ALGOL procedure TRISTURM by Peters and Wilkinson.
  17. C HANDBOOK FOR AUTO. COMP., VOL.II-LINEAR ALGEBRA, 418-439(1971).
  18. C
  19. C This subroutine finds those eigenvectors of a TRIDIAGONAL
  20. C SYMMETRIC matrix corresponding to specified eigenvalues,
  21. C using inverse iteration.
  22. C
  23. C On Input
  24. C
  25. C NM must be set to the row dimension of the two-dimensional
  26. C array parameter, Z, as declared in the calling program
  27. C dimension statement. NM is an INTEGER variable.
  28. C
  29. C N is the order of the matrix. N is an INTEGER variable.
  30. C N must be less than or equal to NM.
  31. C
  32. C D contains the diagonal elements of the symmetric tridiagonal
  33. C matrix. D is a one-dimensional REAL array, dimensioned D(N).
  34. C
  35. C E contains the subdiagonal elements of the symmetric
  36. C tridiagonal matrix in its last N-1 positions. E(1) is
  37. C arbitrary. E is a one-dimensional REAL array, dimensioned
  38. C E(N).
  39. C
  40. C E2 contains the squares of the corresponding elements of E,
  41. C with zeros corresponding to negligible elements of E.
  42. C E(I) is considered negligible if it is not larger than
  43. C the product of the relative machine precision and the sum
  44. C of the magnitudes of D(I) and D(I-1). E2(1) must contain
  45. C 0.0e0 if the eigenvalues are in ascending order, or 2.0e0
  46. C if the eigenvalues are in descending order. If BISECT,
  47. C TRIDIB, or IMTQLV has been used to find the eigenvalues,
  48. C their output E2 array is exactly what is expected here.
  49. C E2 is a one-dimensional REAL array, dimensioned E2(N).
  50. C
  51. C M is the number of specified eigenvalues for which eigenvectors
  52. C are to be determined. M is an INTEGER variable.
  53. C
  54. C W contains the M eigenvalues in ascending or descending order.
  55. C W is a one-dimensional REAL array, dimensioned W(M).
  56. C
  57. C IND contains in its first M positions the submatrix indices
  58. C associated with the corresponding eigenvalues in W --
  59. C 1 for eigenvalues belonging to the first submatrix from
  60. C the top, 2 for those belonging to the second submatrix, etc.
  61. C If BISECT or TRIDIB has been used to determine the
  62. C eigenvalues, their output IND array is suitable for input
  63. C to TINVIT. IND is a one-dimensional INTEGER array,
  64. C dimensioned IND(M).
  65. C
  66. C On Output
  67. C
  68. C ** All input arrays are unaltered.**
  69. C
  70. C Z contains the associated set of orthonormal eigenvectors.
  71. C Any vector which fails to converge is set to zero.
  72. C Z is a two-dimensional REAL array, dimensioned Z(NM,M).
  73. C
  74. C IERR is an INTEGER flag set to
  75. C Zero for normal return,
  76. C -J if the eigenvector corresponding to the J-th
  77. C eigenvalue fails to converge in 5 iterations.
  78. C
  79. C RV1, RV2 and RV3 are one-dimensional REAL arrays used for
  80. C temporary storage. They are used to store the main diagonal
  81. C and the two adjacent diagonals of the triangular matrix
  82. C produced in the inverse iteration process. RV1, RV2 and
  83. C RV3 are dimensioned RV1(N), RV2(N) and RV3(N).
  84. C
  85. C RV4 and RV6 are one-dimensional REAL arrays used for temporary
  86. C storage. RV4 holds the multipliers of the Gaussian
  87. C elimination process. RV6 holds the approximate eigenvectors
  88. C in this process. RV4 and RV6 are dimensioned RV4(N) and
  89. C RV6(N).
  90. C
  91. C Questions and comments should be directed to B. S. Garbow,
  92. C APPLIED MATHEMATICS DIVISION, ARGONNE NATIONAL LABORATORY
  93. C ------------------------------------------------------------------
  94. C
  95. C***REFERENCES B. T. Smith, J. M. Boyle, J. J. Dongarra, B. S. Garbow,
  96. C Y. Ikebe, V. C. Klema and C. B. Moler, Matrix Eigen-
  97. C system Routines - EISPACK Guide, Springer-Verlag,
  98. C 1976.
  99. C***ROUTINES CALLED (NONE)
  100. C***REVISION HISTORY (YYMMDD)
  101. C 760101 DATE WRITTEN
  102. C 890531 Changed all specific intrinsics to generic. (WRB)
  103. C 890831 Modified array declarations. (WRB)
  104. C 890831 REVISION DATE from Version 3.2
  105. C 891214 Prologue converted to Version 4.0 format. (BAB)
  106. C 920501 Reformatted the REFERENCES section. (WRB)
  107. C***END PROLOGUE TINVIT
  108. C
  109. INTEGER I,J,M,N,P,Q,R,S,II,IP,JJ,NM,ITS,TAG,IERR,GROUP
  110. INTEGER IND(*)
  111. REAL D(*),E(*),E2(*),W(*),Z(NM,*)
  112. REAL RV1(*),RV2(*),RV3(*),RV4(*),RV6(*)
  113. REAL U,V,UK,XU,X0,X1,EPS2,EPS3,EPS4,NORM,ORDER
  114. C
  115. C***FIRST EXECUTABLE STATEMENT TINVIT
  116. IERR = 0
  117. IF (M .EQ. 0) GO TO 1001
  118. TAG = 0
  119. ORDER = 1.0E0 - E2(1)
  120. Q = 0
  121. C .......... ESTABLISH AND PROCESS NEXT SUBMATRIX ..........
  122. 100 P = Q + 1
  123. C
  124. DO 120 Q = P, N
  125. IF (Q .EQ. N) GO TO 140
  126. IF (E2(Q+1) .EQ. 0.0E0) GO TO 140
  127. 120 CONTINUE
  128. C .......... FIND VECTORS BY INVERSE ITERATION ..........
  129. 140 TAG = TAG + 1
  130. S = 0
  131. C
  132. DO 920 R = 1, M
  133. IF (IND(R) .NE. TAG) GO TO 920
  134. ITS = 1
  135. X1 = W(R)
  136. IF (S .NE. 0) GO TO 510
  137. C .......... CHECK FOR ISOLATED ROOT ..........
  138. XU = 1.0E0
  139. IF (P .NE. Q) GO TO 490
  140. RV6(P) = 1.0E0
  141. GO TO 870
  142. 490 NORM = ABS(D(P))
  143. IP = P + 1
  144. C
  145. DO 500 I = IP, Q
  146. 500 NORM = MAX(NORM, ABS(D(I)) + ABS(E(I)))
  147. C .......... EPS2 IS THE CRITERION FOR GROUPING,
  148. C EPS3 REPLACES ZERO PIVOTS AND EQUAL
  149. C ROOTS ARE MODIFIED BY EPS3,
  150. C EPS4 IS TAKEN VERY SMALL TO AVOID OVERFLOW ..........
  151. EPS2 = 1.0E-3 * NORM
  152. EPS3 = NORM
  153. 502 EPS3 = 0.5E0*EPS3
  154. IF (NORM + EPS3 .GT. NORM) GO TO 502
  155. UK = SQRT(REAL(Q-P+5))
  156. EPS3 = UK * EPS3
  157. EPS4 = UK * EPS3
  158. UK = EPS4 / UK
  159. S = P
  160. 505 GROUP = 0
  161. GO TO 520
  162. C .......... LOOK FOR CLOSE OR COINCIDENT ROOTS ..........
  163. 510 IF (ABS(X1-X0) .GE. EPS2) GO TO 505
  164. GROUP = GROUP + 1
  165. IF (ORDER * (X1 - X0) .LE. 0.0E0) X1 = X0 + ORDER * EPS3
  166. C .......... ELIMINATION WITH INTERCHANGES AND
  167. C INITIALIZATION OF VECTOR ..........
  168. 520 V = 0.0E0
  169. C
  170. DO 580 I = P, Q
  171. RV6(I) = UK
  172. IF (I .EQ. P) GO TO 560
  173. IF (ABS(E(I)) .LT. ABS(U)) GO TO 540
  174. C .......... WARNING -- A DIVIDE CHECK MAY OCCUR HERE IF
  175. C E2 ARRAY HAS NOT BEEN SPECIFIED CORRECTLY ..........
  176. XU = U / E(I)
  177. RV4(I) = XU
  178. RV1(I-1) = E(I)
  179. RV2(I-1) = D(I) - X1
  180. RV3(I-1) = 0.0E0
  181. IF (I .NE. Q) RV3(I-1) = E(I+1)
  182. U = V - XU * RV2(I-1)
  183. V = -XU * RV3(I-1)
  184. GO TO 580
  185. 540 XU = E(I) / U
  186. RV4(I) = XU
  187. RV1(I-1) = U
  188. RV2(I-1) = V
  189. RV3(I-1) = 0.0E0
  190. 560 U = D(I) - X1 - XU * V
  191. IF (I .NE. Q) V = E(I+1)
  192. 580 CONTINUE
  193. C
  194. IF (U .EQ. 0.0E0) U = EPS3
  195. RV1(Q) = U
  196. RV2(Q) = 0.0E0
  197. RV3(Q) = 0.0E0
  198. C .......... BACK SUBSTITUTION
  199. C FOR I=Q STEP -1 UNTIL P DO -- ..........
  200. 600 DO 620 II = P, Q
  201. I = P + Q - II
  202. RV6(I) = (RV6(I) - U * RV2(I) - V * RV3(I)) / RV1(I)
  203. V = U
  204. U = RV6(I)
  205. 620 CONTINUE
  206. C .......... ORTHOGONALIZE WITH RESPECT TO PREVIOUS
  207. C MEMBERS OF GROUP ..........
  208. IF (GROUP .EQ. 0) GO TO 700
  209. J = R
  210. C
  211. DO 680 JJ = 1, GROUP
  212. 630 J = J - 1
  213. IF (IND(J) .NE. TAG) GO TO 630
  214. XU = 0.0E0
  215. C
  216. DO 640 I = P, Q
  217. 640 XU = XU + RV6(I) * Z(I,J)
  218. C
  219. DO 660 I = P, Q
  220. 660 RV6(I) = RV6(I) - XU * Z(I,J)
  221. C
  222. 680 CONTINUE
  223. C
  224. 700 NORM = 0.0E0
  225. C
  226. DO 720 I = P, Q
  227. 720 NORM = NORM + ABS(RV6(I))
  228. C
  229. IF (NORM .GE. 1.0E0) GO TO 840
  230. C .......... FORWARD SUBSTITUTION ..........
  231. IF (ITS .EQ. 5) GO TO 830
  232. IF (NORM .NE. 0.0E0) GO TO 740
  233. RV6(S) = EPS4
  234. S = S + 1
  235. IF (S .GT. Q) S = P
  236. GO TO 780
  237. 740 XU = EPS4 / NORM
  238. C
  239. DO 760 I = P, Q
  240. 760 RV6(I) = RV6(I) * XU
  241. C .......... ELIMINATION OPERATIONS ON NEXT VECTOR
  242. C ITERATE ..........
  243. 780 DO 820 I = IP, Q
  244. U = RV6(I)
  245. C .......... IF RV1(I-1) .EQ. E(I), A ROW INTERCHANGE
  246. C WAS PERFORMED EARLIER IN THE
  247. C TRIANGULARIZATION PROCESS ..........
  248. IF (RV1(I-1) .NE. E(I)) GO TO 800
  249. U = RV6(I-1)
  250. RV6(I-1) = RV6(I)
  251. 800 RV6(I) = U - RV4(I) * RV6(I-1)
  252. 820 CONTINUE
  253. C
  254. ITS = ITS + 1
  255. GO TO 600
  256. C .......... SET ERROR -- NON-CONVERGED EIGENVECTOR ..........
  257. 830 IERR = -R
  258. XU = 0.0E0
  259. GO TO 870
  260. C .......... NORMALIZE SO THAT SUM OF SQUARES IS
  261. C 1 AND EXPAND TO FULL ORDER ..........
  262. 840 U = 0.0E0
  263. C
  264. DO 860 I = P, Q
  265. 860 U = U + RV6(I)**2
  266. C
  267. XU = 1.0E0 / SQRT(U)
  268. C
  269. 870 DO 880 I = 1, N
  270. 880 Z(I,R) = 0.0E0
  271. C
  272. DO 900 I = P, Q
  273. 900 Z(I,R) = RV6(I) * XU
  274. C
  275. X0 = X1
  276. 920 CONTINUE
  277. C
  278. IF (Q .LT. N) GO TO 100
  279. 1001 RETURN
  280. END