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.

slarrb.f 12 kB

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