bisect.f 8.8 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284
  1. *DECK BISECT
  2. SUBROUTINE BISECT (N, EPS1, D, E, E2, LB, UB, MM, M, W, IND, IERR,
  3. + RV4, RV5)
  4. C***BEGIN PROLOGUE BISECT
  5. C***PURPOSE Compute the eigenvalues of a symmetric tridiagonal matrix
  6. C in a given interval using Sturm sequencing.
  7. C***LIBRARY SLATEC (EISPACK)
  8. C***CATEGORY D4A5, D4C2A
  9. C***TYPE SINGLE PRECISION (BISECT-S)
  10. C***KEYWORDS EIGENVALUES, EISPACK
  11. C***AUTHOR Smith, B. T., et al.
  12. C***DESCRIPTION
  13. C
  14. C This subroutine is a translation of the bisection technique
  15. C in the ALGOL procedure TRISTURM by Peters and Wilkinson.
  16. C HANDBOOK FOR AUTO. COMP., VOL.II-LINEAR ALGEBRA, 418-439(1971).
  17. C
  18. C This subroutine finds those eigenvalues of a TRIDIAGONAL
  19. C SYMMETRIC matrix which lie in a specified interval,
  20. C using bisection.
  21. C
  22. C On INPUT
  23. C
  24. C N is the order of the matrix. N is an INTEGER variable.
  25. C
  26. C EPS1 is an absolute error tolerance for the computed
  27. C eigenvalues. If the input EPS1 is non-positive,
  28. C it is reset for each submatrix to a default value,
  29. C namely, minus the product of the relative machine
  30. C precision and the 1-norm of the submatrix.
  31. C EPS1 is a REAL variable.
  32. C
  33. C D contains the diagonal elements of the input matrix.
  34. C D is a one-dimensional REAL array, dimensioned D(N).
  35. C
  36. C E contains the subdiagonal elements of the input matrix
  37. C in its last N-1 positions. E(1) is arbitrary.
  38. C E is a one-dimensional REAL array, dimensioned E(N).
  39. C
  40. C E2 contains the squares of the corresponding elements of E.
  41. C E2(1) is arbitrary. E2 is a one-dimensional REAL array,
  42. C dimensioned E2(N).
  43. C
  44. C LB and UB define the interval to be searched for eigenvalues.
  45. C If LB is not less than UB, no eigenvalues will be found.
  46. C LB and UB are REAL variables.
  47. C
  48. C MM should be set to an upper bound for the number of
  49. C eigenvalues in the interval. WARNING - If more than
  50. C MM eigenvalues are determined to lie in the interval,
  51. C an error return is made with no eigenvalues found.
  52. C MM is an INTEGER variable.
  53. C
  54. C On OUTPUT
  55. C
  56. C EPS1 is unaltered unless it has been reset to its
  57. C (last) default value.
  58. C
  59. C D and E are unaltered.
  60. C
  61. C Elements of E2, corresponding to elements of E regarded
  62. C as negligible, have been replaced by zero causing the
  63. C matrix to split into a direct sum of submatrices.
  64. C E2(1) is also set to zero.
  65. C
  66. C M is the number of eigenvalues determined to lie in (LB,UB).
  67. C M is an INTEGER variable.
  68. C
  69. C W contains the M eigenvalues in ascending order.
  70. C W is a one-dimensional REAL array, dimensioned W(MM).
  71. C
  72. C IND contains in its first M positions the submatrix indices
  73. C associated with the corresponding eigenvalues in W --
  74. C 1 for eigenvalues belonging to the first submatrix from
  75. C the top, 2 for those belonging to the second submatrix, etc.
  76. C IND is an one-dimensional INTEGER array, dimensioned IND(MM).
  77. C
  78. C IERR is an INTEGER flag set to
  79. C Zero for normal return,
  80. C 3*N+1 if M exceeds MM. In this case, M contains the
  81. C number of eigenvalues determined to lie in
  82. C (LB,UB).
  83. C
  84. C RV4 and RV5 are one-dimensional REAL arrays used for temporary
  85. C storage, dimensioned RV4(N) and RV5(N).
  86. C
  87. C The ALGOL procedure STURMCNT contained in TRISTURM
  88. C appears in BISECT in-line.
  89. C
  90. C Note that subroutine TQL1 or IMTQL1 is generally faster than
  91. C BISECT, if more than N/4 eigenvalues are to be found.
  92. C
  93. C Questions and comments should be directed to B. S. Garbow,
  94. C Applied Mathematics Division, ARGONNE NATIONAL LABORATORY
  95. C ------------------------------------------------------------------
  96. C
  97. C***REFERENCES B. T. Smith, J. M. Boyle, J. J. Dongarra, B. S. Garbow,
  98. C Y. Ikebe, V. C. Klema and C. B. Moler, Matrix Eigen-
  99. C system Routines - EISPACK Guide, Springer-Verlag,
  100. C 1976.
  101. C***ROUTINES CALLED R1MACH
  102. C***REVISION HISTORY (YYMMDD)
  103. C 760101 DATE WRITTEN
  104. C 890531 Changed all specific intrinsics to generic. (WRB)
  105. C 890831 Modified array declarations. (WRB)
  106. C 890831 REVISION DATE from Version 3.2
  107. C 891214 Prologue converted to Version 4.0 format. (BAB)
  108. C 920501 Reformatted the REFERENCES section. (WRB)
  109. C***END PROLOGUE BISECT
  110. C
  111. INTEGER I,J,K,L,M,N,P,Q,R,S,II,MM,M1,M2,TAG,IERR,ISTURM
  112. REAL D(*),E(*),E2(*),W(*),RV4(*),RV5(*)
  113. REAL U,V,LB,T1,T2,UB,XU,X0,X1,EPS1,MACHEP,S1,S2
  114. INTEGER IND(*)
  115. LOGICAL FIRST
  116. C
  117. SAVE FIRST, MACHEP
  118. DATA FIRST /.TRUE./
  119. C***FIRST EXECUTABLE STATEMENT BISECT
  120. IF (FIRST) THEN
  121. MACHEP = R1MACH(4)
  122. ENDIF
  123. FIRST = .FALSE.
  124. C
  125. IERR = 0
  126. TAG = 0
  127. T1 = LB
  128. T2 = UB
  129. C .......... LOOK FOR SMALL SUB-DIAGONAL ENTRIES ..........
  130. DO 40 I = 1, N
  131. IF (I .EQ. 1) GO TO 20
  132. S1 = ABS(D(I)) + ABS(D(I-1))
  133. S2 = S1 + ABS(E(I))
  134. IF (S2 .GT. S1) GO TO 40
  135. 20 E2(I) = 0.0E0
  136. 40 CONTINUE
  137. C .......... DETERMINE THE NUMBER OF EIGENVALUES
  138. C IN THE INTERVAL ..........
  139. P = 1
  140. Q = N
  141. X1 = UB
  142. ISTURM = 1
  143. GO TO 320
  144. 60 M = S
  145. X1 = LB
  146. ISTURM = 2
  147. GO TO 320
  148. 80 M = M - S
  149. IF (M .GT. MM) GO TO 980
  150. Q = 0
  151. R = 0
  152. C .......... ESTABLISH AND PROCESS NEXT SUBMATRIX, REFINING
  153. C INTERVAL BY THE GERSCHGORIN BOUNDS ..........
  154. 100 IF (R .EQ. M) GO TO 1001
  155. TAG = TAG + 1
  156. P = Q + 1
  157. XU = D(P)
  158. X0 = D(P)
  159. U = 0.0E0
  160. C
  161. DO 120 Q = P, N
  162. X1 = U
  163. U = 0.0E0
  164. V = 0.0E0
  165. IF (Q .EQ. N) GO TO 110
  166. U = ABS(E(Q+1))
  167. V = E2(Q+1)
  168. 110 XU = MIN(D(Q)-(X1+U),XU)
  169. X0 = MAX(D(Q)+(X1+U),X0)
  170. IF (V .EQ. 0.0E0) GO TO 140
  171. 120 CONTINUE
  172. C
  173. 140 X1 = MAX(ABS(XU),ABS(X0)) * MACHEP
  174. IF (EPS1 .LE. 0.0E0) EPS1 = -X1
  175. IF (P .NE. Q) GO TO 180
  176. C .......... CHECK FOR ISOLATED ROOT WITHIN INTERVAL ..........
  177. IF (T1 .GT. D(P) .OR. D(P) .GE. T2) GO TO 940
  178. M1 = P
  179. M2 = P
  180. RV5(P) = D(P)
  181. GO TO 900
  182. 180 X1 = X1 * (Q-P+1)
  183. LB = MAX(T1,XU-X1)
  184. UB = MIN(T2,X0+X1)
  185. X1 = LB
  186. ISTURM = 3
  187. GO TO 320
  188. 200 M1 = S + 1
  189. X1 = UB
  190. ISTURM = 4
  191. GO TO 320
  192. 220 M2 = S
  193. IF (M1 .GT. M2) GO TO 940
  194. C .......... FIND ROOTS BY BISECTION ..........
  195. X0 = UB
  196. ISTURM = 5
  197. C
  198. DO 240 I = M1, M2
  199. RV5(I) = UB
  200. RV4(I) = LB
  201. 240 CONTINUE
  202. C .......... LOOP FOR K-TH EIGENVALUE
  203. C FOR K=M2 STEP -1 UNTIL M1 DO --
  204. C (-DO- NOT USED TO LEGALIZE -COMPUTED GO TO-) ..........
  205. K = M2
  206. 250 XU = LB
  207. C .......... FOR I=K STEP -1 UNTIL M1 DO -- ..........
  208. DO 260 II = M1, K
  209. I = M1 + K - II
  210. IF (XU .GE. RV4(I)) GO TO 260
  211. XU = RV4(I)
  212. GO TO 280
  213. 260 CONTINUE
  214. C
  215. 280 IF (X0 .GT. RV5(K)) X0 = RV5(K)
  216. C .......... NEXT BISECTION STEP ..........
  217. 300 X1 = (XU + X0) * 0.5E0
  218. S1 = 2.0E0*(ABS(XU) + ABS(X0) + ABS(EPS1))
  219. S2 = S1 + ABS(X0 - XU)
  220. IF (S2 .EQ. S1) GO TO 420
  221. C .......... IN-LINE PROCEDURE FOR STURM SEQUENCE ..........
  222. 320 S = P - 1
  223. U = 1.0E0
  224. C
  225. DO 340 I = P, Q
  226. IF (U .NE. 0.0E0) GO TO 325
  227. V = ABS(E(I)) / MACHEP
  228. IF (E2(I) .EQ. 0.0E0) V = 0.0E0
  229. GO TO 330
  230. 325 V = E2(I) / U
  231. 330 U = D(I) - X1 - V
  232. IF (U .LT. 0.0E0) S = S + 1
  233. 340 CONTINUE
  234. C
  235. GO TO (60,80,200,220,360), ISTURM
  236. C .......... REFINE INTERVALS ..........
  237. 360 IF (S .GE. K) GO TO 400
  238. XU = X1
  239. IF (S .GE. M1) GO TO 380
  240. RV4(M1) = X1
  241. GO TO 300
  242. 380 RV4(S+1) = X1
  243. IF (RV5(S) .GT. X1) RV5(S) = X1
  244. GO TO 300
  245. 400 X0 = X1
  246. GO TO 300
  247. C .......... K-TH EIGENVALUE FOUND ..........
  248. 420 RV5(K) = X1
  249. K = K - 1
  250. IF (K .GE. M1) GO TO 250
  251. C .......... ORDER EIGENVALUES TAGGED WITH THEIR
  252. C SUBMATRIX ASSOCIATIONS ..........
  253. 900 S = R
  254. R = R + M2 - M1 + 1
  255. J = 1
  256. K = M1
  257. C
  258. DO 920 L = 1, R
  259. IF (J .GT. S) GO TO 910
  260. IF (K .GT. M2) GO TO 940
  261. IF (RV5(K) .GE. W(L)) GO TO 915
  262. C
  263. DO 905 II = J, S
  264. I = L + S - II
  265. W(I+1) = W(I)
  266. IND(I+1) = IND(I)
  267. 905 CONTINUE
  268. C
  269. 910 W(L) = RV5(K)
  270. IND(L) = TAG
  271. K = K + 1
  272. GO TO 920
  273. 915 J = J + 1
  274. 920 CONTINUE
  275. C
  276. 940 IF (Q .LT. N) GO TO 100
  277. GO TO 1001
  278. C .......... SET ERROR -- UNDERESTIMATE OF NUMBER OF
  279. C EIGENVALUES IN INTERVAL ..........
  280. 980 IERR = 3 * N + 1
  281. 1001 LB = T1
  282. UB = T2
  283. RETURN
  284. END