You can not select more than 25 topics Topics must start with a chinese character,a letter or number, can include dashes ('-') and can be up to 35 characters long.

slarrj.f 11 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376
  1. *> \brief \b SLARRJ performs refinement of the initial estimates of the eigenvalues of the matrix T.
  2. *
  3. * =========== DOCUMENTATION ===========
  4. *
  5. * Online html documentation available at
  6. * http://www.netlib.org/lapack/explore-html/
  7. *
  8. *> \htmlonly
  9. *> Download SLARRJ + dependencies
  10. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slarrj.f">
  11. *> [TGZ]</a>
  12. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slarrj.f">
  13. *> [ZIP]</a>
  14. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slarrj.f">
  15. *> [TXT]</a>
  16. *> \endhtmlonly
  17. *
  18. * Definition:
  19. * ===========
  20. *
  21. * SUBROUTINE SLARRJ( N, D, E2, IFIRST, ILAST,
  22. * RTOL, OFFSET, W, WERR, WORK, IWORK,
  23. * PIVMIN, SPDIAM, INFO )
  24. *
  25. * .. Scalar Arguments ..
  26. * INTEGER IFIRST, ILAST, INFO, N, OFFSET
  27. * REAL PIVMIN, RTOL, SPDIAM
  28. * ..
  29. * .. Array Arguments ..
  30. * INTEGER IWORK( * )
  31. * REAL D( * ), E2( * ), W( * ),
  32. * $ WERR( * ), WORK( * )
  33. * ..
  34. *
  35. *
  36. *> \par Purpose:
  37. * =============
  38. *>
  39. *> \verbatim
  40. *>
  41. *> Given the initial eigenvalue approximations of T, SLARRJ
  42. *> does bisection to refine the eigenvalues of T,
  43. *> W( IFIRST-OFFSET ) through W( ILAST-OFFSET ), to more accuracy. Initial
  44. *> guesses for these eigenvalues are input in W, the corresponding estimate
  45. *> of the error in these guesses in WERR. During bisection, intervals
  46. *> [left, right] are maintained by storing their mid-points and
  47. *> semi-widths in the arrays W and WERR respectively.
  48. *> \endverbatim
  49. *
  50. * Arguments:
  51. * ==========
  52. *
  53. *> \param[in] N
  54. *> \verbatim
  55. *> N is INTEGER
  56. *> The order of the matrix.
  57. *> \endverbatim
  58. *>
  59. *> \param[in] D
  60. *> \verbatim
  61. *> D is REAL array, dimension (N)
  62. *> The N diagonal elements of T.
  63. *> \endverbatim
  64. *>
  65. *> \param[in] E2
  66. *> \verbatim
  67. *> E2 is REAL array, dimension (N-1)
  68. *> The Squares of the (N-1) subdiagonal elements of T.
  69. *> \endverbatim
  70. *>
  71. *> \param[in] IFIRST
  72. *> \verbatim
  73. *> IFIRST is INTEGER
  74. *> The index of the first eigenvalue to be computed.
  75. *> \endverbatim
  76. *>
  77. *> \param[in] ILAST
  78. *> \verbatim
  79. *> ILAST is INTEGER
  80. *> The index of the last eigenvalue to be computed.
  81. *> \endverbatim
  82. *>
  83. *> \param[in] RTOL
  84. *> \verbatim
  85. *> RTOL is REAL
  86. *> Tolerance for the convergence of the bisection intervals.
  87. *> An interval [LEFT,RIGHT] has converged if
  88. *> RIGHT-LEFT < RTOL*MAX(|LEFT|,|RIGHT|).
  89. *> \endverbatim
  90. *>
  91. *> \param[in] OFFSET
  92. *> \verbatim
  93. *> OFFSET is INTEGER
  94. *> Offset for the arrays W and WERR, i.e., the IFIRST-OFFSET
  95. *> through ILAST-OFFSET elements of these arrays are to be used.
  96. *> \endverbatim
  97. *>
  98. *> \param[in,out] W
  99. *> \verbatim
  100. *> W is REAL array, dimension (N)
  101. *> On input, W( IFIRST-OFFSET ) through W( ILAST-OFFSET ) are
  102. *> estimates of the eigenvalues of L D L^T indexed IFIRST through
  103. *> ILAST.
  104. *> On output, these estimates are refined.
  105. *> \endverbatim
  106. *>
  107. *> \param[in,out] WERR
  108. *> \verbatim
  109. *> WERR is REAL array, dimension (N)
  110. *> On input, WERR( IFIRST-OFFSET ) through WERR( ILAST-OFFSET ) are
  111. *> the errors in the estimates of the corresponding elements in W.
  112. *> On output, these errors are refined.
  113. *> \endverbatim
  114. *>
  115. *> \param[out] WORK
  116. *> \verbatim
  117. *> WORK is REAL array, dimension (2*N)
  118. *> Workspace.
  119. *> \endverbatim
  120. *>
  121. *> \param[out] IWORK
  122. *> \verbatim
  123. *> IWORK is INTEGER array, dimension (2*N)
  124. *> Workspace.
  125. *> \endverbatim
  126. *>
  127. *> \param[in] PIVMIN
  128. *> \verbatim
  129. *> PIVMIN is REAL
  130. *> The minimum pivot in the Sturm sequence for T.
  131. *> \endverbatim
  132. *>
  133. *> \param[in] SPDIAM
  134. *> \verbatim
  135. *> SPDIAM is REAL
  136. *> The spectral diameter of T.
  137. *> \endverbatim
  138. *>
  139. *> \param[out] INFO
  140. *> \verbatim
  141. *> INFO is INTEGER
  142. *> Error flag.
  143. *> \endverbatim
  144. *
  145. * Authors:
  146. * ========
  147. *
  148. *> \author Univ. of Tennessee
  149. *> \author Univ. of California Berkeley
  150. *> \author Univ. of Colorado Denver
  151. *> \author NAG Ltd.
  152. *
  153. *> \ingroup OTHERauxiliary
  154. *
  155. *> \par Contributors:
  156. * ==================
  157. *>
  158. *> Beresford Parlett, University of California, Berkeley, USA \n
  159. *> Jim Demmel, University of California, Berkeley, USA \n
  160. *> Inderjit Dhillon, University of Texas, Austin, USA \n
  161. *> Osni Marques, LBNL/NERSC, USA \n
  162. *> Christof Voemel, University of California, Berkeley, USA
  163. *
  164. * =====================================================================
  165. SUBROUTINE SLARRJ( N, D, E2, IFIRST, ILAST,
  166. $ RTOL, OFFSET, W, WERR, WORK, IWORK,
  167. $ PIVMIN, SPDIAM, INFO )
  168. *
  169. * -- LAPACK auxiliary routine --
  170. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  171. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  172. *
  173. * .. Scalar Arguments ..
  174. INTEGER IFIRST, ILAST, INFO, N, OFFSET
  175. REAL PIVMIN, RTOL, SPDIAM
  176. * ..
  177. * .. Array Arguments ..
  178. INTEGER IWORK( * )
  179. REAL D( * ), E2( * ), W( * ),
  180. $ WERR( * ), WORK( * )
  181. * ..
  182. *
  183. * =====================================================================
  184. *
  185. * .. Parameters ..
  186. REAL ZERO, ONE, TWO, HALF
  187. PARAMETER ( ZERO = 0.0E0, ONE = 1.0E0, TWO = 2.0E0,
  188. $ HALF = 0.5E0 )
  189. INTEGER MAXITR
  190. * ..
  191. * .. Local Scalars ..
  192. INTEGER CNT, I, I1, I2, II, ITER, J, K, NEXT, NINT,
  193. $ OLNINT, P, PREV, SAVI1
  194. REAL DPLUS, FAC, LEFT, MID, RIGHT, S, TMP, WIDTH
  195. *
  196. * ..
  197. * .. Intrinsic Functions ..
  198. INTRINSIC ABS, MAX
  199. * ..
  200. * .. Executable Statements ..
  201. *
  202. INFO = 0
  203. *
  204. * Quick return if possible
  205. *
  206. IF( N.LE.0 ) THEN
  207. RETURN
  208. END IF
  209. *
  210. MAXITR = INT( ( LOG( SPDIAM+PIVMIN )-LOG( PIVMIN ) ) /
  211. $ LOG( TWO ) ) + 2
  212. *
  213. * Initialize unconverged intervals in [ WORK(2*I-1), WORK(2*I) ].
  214. * The Sturm Count, Count( WORK(2*I-1) ) is arranged to be I-1, while
  215. * Count( WORK(2*I) ) is stored in IWORK( 2*I ). The integer IWORK( 2*I-1 )
  216. * for an unconverged interval is set to the index of the next unconverged
  217. * interval, and is -1 or 0 for a converged interval. Thus a linked
  218. * list of unconverged intervals is set up.
  219. *
  220. I1 = IFIRST
  221. I2 = ILAST
  222. * The number of unconverged intervals
  223. NINT = 0
  224. * The last unconverged interval found
  225. PREV = 0
  226. DO 75 I = I1, I2
  227. K = 2*I
  228. II = I - OFFSET
  229. LEFT = W( II ) - WERR( II )
  230. MID = W(II)
  231. RIGHT = W( II ) + WERR( II )
  232. WIDTH = RIGHT - MID
  233. TMP = MAX( ABS( LEFT ), ABS( RIGHT ) )
  234. * The following test prevents the test of converged intervals
  235. IF( WIDTH.LT.RTOL*TMP ) THEN
  236. * This interval has already converged and does not need refinement.
  237. * (Note that the gaps might change through refining the
  238. * eigenvalues, however, they can only get bigger.)
  239. * Remove it from the list.
  240. IWORK( K-1 ) = -1
  241. * Make sure that I1 always points to the first unconverged interval
  242. IF((I.EQ.I1).AND.(I.LT.I2)) I1 = I + 1
  243. IF((PREV.GE.I1).AND.(I.LE.I2)) IWORK( 2*PREV-1 ) = I + 1
  244. ELSE
  245. * unconverged interval found
  246. PREV = I
  247. * Make sure that [LEFT,RIGHT] contains the desired eigenvalue
  248. *
  249. * Do while( CNT(LEFT).GT.I-1 )
  250. *
  251. FAC = ONE
  252. 20 CONTINUE
  253. CNT = 0
  254. S = LEFT
  255. DPLUS = D( 1 ) - S
  256. IF( DPLUS.LT.ZERO ) CNT = CNT + 1
  257. DO 30 J = 2, N
  258. DPLUS = D( J ) - S - E2( J-1 )/DPLUS
  259. IF( DPLUS.LT.ZERO ) CNT = CNT + 1
  260. 30 CONTINUE
  261. IF( CNT.GT.I-1 ) THEN
  262. LEFT = LEFT - WERR( II )*FAC
  263. FAC = TWO*FAC
  264. GO TO 20
  265. END IF
  266. *
  267. * Do while( CNT(RIGHT).LT.I )
  268. *
  269. FAC = ONE
  270. 50 CONTINUE
  271. CNT = 0
  272. S = RIGHT
  273. DPLUS = D( 1 ) - S
  274. IF( DPLUS.LT.ZERO ) CNT = CNT + 1
  275. DO 60 J = 2, N
  276. DPLUS = D( J ) - S - E2( J-1 )/DPLUS
  277. IF( DPLUS.LT.ZERO ) CNT = CNT + 1
  278. 60 CONTINUE
  279. IF( CNT.LT.I ) THEN
  280. RIGHT = RIGHT + WERR( II )*FAC
  281. FAC = TWO*FAC
  282. GO TO 50
  283. END IF
  284. NINT = NINT + 1
  285. IWORK( K-1 ) = I + 1
  286. IWORK( K ) = CNT
  287. END IF
  288. WORK( K-1 ) = LEFT
  289. WORK( K ) = RIGHT
  290. 75 CONTINUE
  291. SAVI1 = I1
  292. *
  293. * Do while( NINT.GT.0 ), i.e. there are still unconverged intervals
  294. * and while (ITER.LT.MAXITR)
  295. *
  296. ITER = 0
  297. 80 CONTINUE
  298. PREV = I1 - 1
  299. I = I1
  300. OLNINT = NINT
  301. DO 100 P = 1, OLNINT
  302. K = 2*I
  303. II = I - OFFSET
  304. NEXT = IWORK( K-1 )
  305. LEFT = WORK( K-1 )
  306. RIGHT = WORK( K )
  307. MID = HALF*( LEFT + RIGHT )
  308. * semiwidth of interval
  309. WIDTH = RIGHT - MID
  310. TMP = MAX( ABS( LEFT ), ABS( RIGHT ) )
  311. IF( ( WIDTH.LT.RTOL*TMP ) .OR.
  312. $ (ITER.EQ.MAXITR) )THEN
  313. * reduce number of unconverged intervals
  314. NINT = NINT - 1
  315. * Mark interval as converged.
  316. IWORK( K-1 ) = 0
  317. IF( I1.EQ.I ) THEN
  318. I1 = NEXT
  319. ELSE
  320. * Prev holds the last unconverged interval previously examined
  321. IF(PREV.GE.I1) IWORK( 2*PREV-1 ) = NEXT
  322. END IF
  323. I = NEXT
  324. GO TO 100
  325. END IF
  326. PREV = I
  327. *
  328. * Perform one bisection step
  329. *
  330. CNT = 0
  331. S = MID
  332. DPLUS = D( 1 ) - S
  333. IF( DPLUS.LT.ZERO ) CNT = CNT + 1
  334. DO 90 J = 2, N
  335. DPLUS = D( J ) - S - E2( J-1 )/DPLUS
  336. IF( DPLUS.LT.ZERO ) CNT = CNT + 1
  337. 90 CONTINUE
  338. IF( CNT.LE.I-1 ) THEN
  339. WORK( K-1 ) = MID
  340. ELSE
  341. WORK( K ) = MID
  342. END IF
  343. I = NEXT
  344. 100 CONTINUE
  345. ITER = ITER + 1
  346. * do another loop if there are still unconverged intervals
  347. * However, in the last iteration, all intervals are accepted
  348. * since this is the best we can do.
  349. IF( ( NINT.GT.0 ).AND.(ITER.LE.MAXITR) ) GO TO 80
  350. *
  351. *
  352. * At this point, all the intervals have converged
  353. DO 110 I = SAVI1, ILAST
  354. K = 2*I
  355. II = I - OFFSET
  356. * All intervals marked by '0' have been refined.
  357. IF( IWORK( K-1 ).EQ.0 ) THEN
  358. W( II ) = HALF*( WORK( K-1 )+WORK( K ) )
  359. WERR( II ) = WORK( K ) - W( II )
  360. END IF
  361. 110 CONTINUE
  362. *
  363. RETURN
  364. *
  365. * End of SLARRJ
  366. *
  367. END