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.

slarrf.f 15 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492
  1. *> \brief \b SLARRF finds a new relatively robust representation such that at least one of the eigenvalues is relatively isolated.
  2. *
  3. * =========== DOCUMENTATION ===========
  4. *
  5. * Online html documentation available at
  6. * http://www.netlib.org/lapack/explore-html/
  7. *
  8. *> \htmlonly
  9. *> Download SLARRF + dependencies
  10. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slarrf.f">
  11. *> [TGZ]</a>
  12. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slarrf.f">
  13. *> [ZIP]</a>
  14. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slarrf.f">
  15. *> [TXT]</a>
  16. *> \endhtmlonly
  17. *
  18. * Definition:
  19. * ===========
  20. *
  21. * SUBROUTINE SLARRF( N, D, L, LD, CLSTRT, CLEND,
  22. * W, WGAP, WERR,
  23. * SPDIAM, CLGAPL, CLGAPR, PIVMIN, SIGMA,
  24. * DPLUS, LPLUS, WORK, INFO )
  25. *
  26. * .. Scalar Arguments ..
  27. * INTEGER CLSTRT, CLEND, INFO, N
  28. * REAL CLGAPL, CLGAPR, PIVMIN, SIGMA, SPDIAM
  29. * ..
  30. * .. Array Arguments ..
  31. * REAL D( * ), DPLUS( * ), L( * ), LD( * ),
  32. * $ LPLUS( * ), W( * ), WGAP( * ), WERR( * ), WORK( * )
  33. * ..
  34. *
  35. *
  36. *> \par Purpose:
  37. * =============
  38. *>
  39. *> \verbatim
  40. *>
  41. *> Given the initial representation L D L^T and its cluster of close
  42. *> eigenvalues (in a relative measure), W( CLSTRT ), W( CLSTRT+1 ), ...
  43. *> W( CLEND ), SLARRF finds a new relatively robust representation
  44. *> L D L^T - SIGMA I = L(+) D(+) L(+)^T such that at least one of the
  45. *> eigenvalues of L(+) D(+) L(+)^T is relatively isolated.
  46. *> \endverbatim
  47. *
  48. * Arguments:
  49. * ==========
  50. *
  51. *> \param[in] N
  52. *> \verbatim
  53. *> N is INTEGER
  54. *> The order of the matrix (subblock, if the matrix split).
  55. *> \endverbatim
  56. *>
  57. *> \param[in] D
  58. *> \verbatim
  59. *> D is REAL array, dimension (N)
  60. *> The N diagonal elements of the diagonal matrix D.
  61. *> \endverbatim
  62. *>
  63. *> \param[in] L
  64. *> \verbatim
  65. *> L is REAL array, dimension (N-1)
  66. *> The (N-1) subdiagonal elements of the unit bidiagonal
  67. *> matrix L.
  68. *> \endverbatim
  69. *>
  70. *> \param[in] LD
  71. *> \verbatim
  72. *> LD is REAL array, dimension (N-1)
  73. *> The (N-1) elements L(i)*D(i).
  74. *> \endverbatim
  75. *>
  76. *> \param[in] CLSTRT
  77. *> \verbatim
  78. *> CLSTRT is INTEGER
  79. *> The index of the first eigenvalue in the cluster.
  80. *> \endverbatim
  81. *>
  82. *> \param[in] CLEND
  83. *> \verbatim
  84. *> CLEND is INTEGER
  85. *> The index of the last eigenvalue in the cluster.
  86. *> \endverbatim
  87. *>
  88. *> \param[in] W
  89. *> \verbatim
  90. *> W is REAL array, dimension
  91. *> dimension is >= (CLEND-CLSTRT+1)
  92. *> The eigenvalue APPROXIMATIONS of L D L^T in ascending order.
  93. *> W( CLSTRT ) through W( CLEND ) form the cluster of relatively
  94. *> close eigenalues.
  95. *> \endverbatim
  96. *>
  97. *> \param[in,out] WGAP
  98. *> \verbatim
  99. *> WGAP is REAL array, dimension
  100. *> dimension is >= (CLEND-CLSTRT+1)
  101. *> The separation from the right neighbor eigenvalue in W.
  102. *> \endverbatim
  103. *>
  104. *> \param[in] WERR
  105. *> \verbatim
  106. *> WERR is REAL array, dimension
  107. *> dimension is >= (CLEND-CLSTRT+1)
  108. *> WERR contain the semiwidth of the uncertainty
  109. *> interval of the corresponding eigenvalue APPROXIMATION in W
  110. *> \endverbatim
  111. *>
  112. *> \param[in] SPDIAM
  113. *> \verbatim
  114. *> SPDIAM is REAL
  115. *> estimate of the spectral diameter obtained from the
  116. *> Gerschgorin intervals
  117. *> \endverbatim
  118. *>
  119. *> \param[in] CLGAPL
  120. *> \verbatim
  121. *> CLGAPL is REAL
  122. *> \endverbatim
  123. *>
  124. *> \param[in] CLGAPR
  125. *> \verbatim
  126. *> CLGAPR is REAL
  127. *> absolute gap on each end of the cluster.
  128. *> Set by the calling routine to protect against shifts too close
  129. *> to eigenvalues outside the cluster.
  130. *> \endverbatim
  131. *>
  132. *> \param[in] PIVMIN
  133. *> \verbatim
  134. *> PIVMIN is REAL
  135. *> The minimum pivot allowed in the Sturm sequence.
  136. *> \endverbatim
  137. *>
  138. *> \param[out] SIGMA
  139. *> \verbatim
  140. *> SIGMA is REAL
  141. *> The shift used to form L(+) D(+) L(+)^T.
  142. *> \endverbatim
  143. *>
  144. *> \param[out] DPLUS
  145. *> \verbatim
  146. *> DPLUS is REAL array, dimension (N)
  147. *> The N diagonal elements of the diagonal matrix D(+).
  148. *> \endverbatim
  149. *>
  150. *> \param[out] LPLUS
  151. *> \verbatim
  152. *> LPLUS is REAL array, dimension (N-1)
  153. *> The first (N-1) elements of LPLUS contain the subdiagonal
  154. *> elements of the unit bidiagonal matrix L(+).
  155. *> \endverbatim
  156. *>
  157. *> \param[out] WORK
  158. *> \verbatim
  159. *> WORK is REAL array, dimension (2*N)
  160. *> Workspace.
  161. *> \endverbatim
  162. *>
  163. *> \param[out] INFO
  164. *> \verbatim
  165. *> INFO is INTEGER
  166. *> Signals processing OK (=0) or failure (=1)
  167. *> \endverbatim
  168. *
  169. * Authors:
  170. * ========
  171. *
  172. *> \author Univ. of Tennessee
  173. *> \author Univ. of California Berkeley
  174. *> \author Univ. of Colorado Denver
  175. *> \author NAG Ltd.
  176. *
  177. *> \ingroup OTHERauxiliary
  178. *
  179. *> \par Contributors:
  180. * ==================
  181. *>
  182. *> Beresford Parlett, University of California, Berkeley, USA \n
  183. *> Jim Demmel, University of California, Berkeley, USA \n
  184. *> Inderjit Dhillon, University of Texas, Austin, USA \n
  185. *> Osni Marques, LBNL/NERSC, USA \n
  186. *> Christof Voemel, University of California, Berkeley, USA
  187. *
  188. * =====================================================================
  189. SUBROUTINE SLARRF( N, D, L, LD, CLSTRT, CLEND,
  190. $ W, WGAP, WERR,
  191. $ SPDIAM, CLGAPL, CLGAPR, PIVMIN, SIGMA,
  192. $ DPLUS, LPLUS, WORK, INFO )
  193. *
  194. * -- LAPACK auxiliary routine --
  195. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  196. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  197. *
  198. * .. Scalar Arguments ..
  199. INTEGER CLSTRT, CLEND, INFO, N
  200. REAL CLGAPL, CLGAPR, PIVMIN, SIGMA, SPDIAM
  201. * ..
  202. * .. Array Arguments ..
  203. REAL D( * ), DPLUS( * ), L( * ), LD( * ),
  204. $ LPLUS( * ), W( * ), WGAP( * ), WERR( * ), WORK( * )
  205. * ..
  206. *
  207. * =====================================================================
  208. *
  209. * .. Parameters ..
  210. REAL MAXGROWTH1, MAXGROWTH2, ONE, QUART, TWO
  211. PARAMETER ( ONE = 1.0E0, TWO = 2.0E0,
  212. $ QUART = 0.25E0,
  213. $ MAXGROWTH1 = 8.E0,
  214. $ MAXGROWTH2 = 8.E0 )
  215. * ..
  216. * .. Local Scalars ..
  217. LOGICAL DORRR1, FORCER, NOFAIL, SAWNAN1, SAWNAN2, TRYRRR1
  218. INTEGER I, INDX, KTRY, KTRYMAX, SLEFT, SRIGHT, SHIFT
  219. PARAMETER ( KTRYMAX = 1, SLEFT = 1, SRIGHT = 2 )
  220. REAL AVGAP, BESTSHIFT, CLWDTH, EPS, FACT, FAIL,
  221. $ FAIL2, GROWTHBOUND, LDELTA, LDMAX, LSIGMA,
  222. $ MAX1, MAX2, MINGAP, OLDP, PROD, RDELTA, RDMAX,
  223. $ RRR1, RRR2, RSIGMA, S, SMLGROWTH, TMP, ZNM2
  224. * ..
  225. * .. External Functions ..
  226. LOGICAL SISNAN
  227. REAL SLAMCH
  228. EXTERNAL SISNAN, SLAMCH
  229. * ..
  230. * .. External Subroutines ..
  231. EXTERNAL SCOPY
  232. * ..
  233. * .. Intrinsic Functions ..
  234. INTRINSIC ABS
  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. FACT = REAL(2**KTRYMAX)
  247. EPS = SLAMCH( 'Precision' )
  248. SHIFT = 0
  249. FORCER = .FALSE.
  250. * Note that we cannot guarantee that for any of the shifts tried,
  251. * the factorization has a small or even moderate element growth.
  252. * There could be Ritz values at both ends of the cluster and despite
  253. * backing off, there are examples where all factorizations tried
  254. * (in IEEE mode, allowing zero pivots & infinities) have INFINITE
  255. * element growth.
  256. * For this reason, we should use PIVMIN in this subroutine so that at
  257. * least the L D L^T factorization exists. It can be checked afterwards
  258. * whether the element growth caused bad residuals/orthogonality.
  259. * Decide whether the code should accept the best among all
  260. * representations despite large element growth or signal INFO=1
  261. * Setting NOFAIL to .FALSE. for quick fix for bug 113
  262. NOFAIL = .FALSE.
  263. *
  264. * Compute the average gap length of the cluster
  265. CLWDTH = ABS(W(CLEND)-W(CLSTRT)) + WERR(CLEND) + WERR(CLSTRT)
  266. AVGAP = CLWDTH / REAL(CLEND-CLSTRT)
  267. MINGAP = MIN(CLGAPL, CLGAPR)
  268. * Initial values for shifts to both ends of cluster
  269. LSIGMA = MIN(W( CLSTRT ),W( CLEND )) - WERR( CLSTRT )
  270. RSIGMA = MAX(W( CLSTRT ),W( CLEND )) + WERR( CLEND )
  271. * Use a small fudge to make sure that we really shift to the outside
  272. LSIGMA = LSIGMA - ABS(LSIGMA)* TWO * EPS
  273. RSIGMA = RSIGMA + ABS(RSIGMA)* TWO * EPS
  274. * Compute upper bounds for how much to back off the initial shifts
  275. LDMAX = QUART * MINGAP + TWO * PIVMIN
  276. RDMAX = QUART * MINGAP + TWO * PIVMIN
  277. LDELTA = MAX(AVGAP,WGAP( CLSTRT ))/FACT
  278. RDELTA = MAX(AVGAP,WGAP( CLEND-1 ))/FACT
  279. *
  280. * Initialize the record of the best representation found
  281. *
  282. S = SLAMCH( 'S' )
  283. SMLGROWTH = ONE / S
  284. FAIL = REAL(N-1)*MINGAP/(SPDIAM*EPS)
  285. FAIL2 = REAL(N-1)*MINGAP/(SPDIAM*SQRT(EPS))
  286. BESTSHIFT = LSIGMA
  287. *
  288. * while (KTRY <= KTRYMAX)
  289. KTRY = 0
  290. GROWTHBOUND = MAXGROWTH1*SPDIAM
  291. 5 CONTINUE
  292. SAWNAN1 = .FALSE.
  293. SAWNAN2 = .FALSE.
  294. * Ensure that we do not back off too much of the initial shifts
  295. LDELTA = MIN(LDMAX,LDELTA)
  296. RDELTA = MIN(RDMAX,RDELTA)
  297. * Compute the element growth when shifting to both ends of the cluster
  298. * accept the shift if there is no element growth at one of the two ends
  299. * Left end
  300. S = -LSIGMA
  301. DPLUS( 1 ) = D( 1 ) + S
  302. IF(ABS(DPLUS(1)).LT.PIVMIN) THEN
  303. DPLUS(1) = -PIVMIN
  304. * Need to set SAWNAN1 because refined RRR test should not be used
  305. * in this case
  306. SAWNAN1 = .TRUE.
  307. ENDIF
  308. MAX1 = ABS( DPLUS( 1 ) )
  309. DO 6 I = 1, N - 1
  310. LPLUS( I ) = LD( I ) / DPLUS( I )
  311. S = S*LPLUS( I )*L( I ) - LSIGMA
  312. DPLUS( I+1 ) = D( I+1 ) + S
  313. IF(ABS(DPLUS(I+1)).LT.PIVMIN) THEN
  314. DPLUS(I+1) = -PIVMIN
  315. * Need to set SAWNAN1 because refined RRR test should not be used
  316. * in this case
  317. SAWNAN1 = .TRUE.
  318. ENDIF
  319. MAX1 = MAX( MAX1,ABS(DPLUS(I+1)) )
  320. 6 CONTINUE
  321. SAWNAN1 = SAWNAN1 .OR. SISNAN( MAX1 )
  322. IF( FORCER .OR.
  323. $ (MAX1.LE.GROWTHBOUND .AND. .NOT.SAWNAN1 ) ) THEN
  324. SIGMA = LSIGMA
  325. SHIFT = SLEFT
  326. GOTO 100
  327. ENDIF
  328. * Right end
  329. S = -RSIGMA
  330. WORK( 1 ) = D( 1 ) + S
  331. IF(ABS(WORK(1)).LT.PIVMIN) THEN
  332. WORK(1) = -PIVMIN
  333. * Need to set SAWNAN2 because refined RRR test should not be used
  334. * in this case
  335. SAWNAN2 = .TRUE.
  336. ENDIF
  337. MAX2 = ABS( WORK( 1 ) )
  338. DO 7 I = 1, N - 1
  339. WORK( N+I ) = LD( I ) / WORK( I )
  340. S = S*WORK( N+I )*L( I ) - RSIGMA
  341. WORK( I+1 ) = D( I+1 ) + S
  342. IF(ABS(WORK(I+1)).LT.PIVMIN) THEN
  343. WORK(I+1) = -PIVMIN
  344. * Need to set SAWNAN2 because refined RRR test should not be used
  345. * in this case
  346. SAWNAN2 = .TRUE.
  347. ENDIF
  348. MAX2 = MAX( MAX2,ABS(WORK(I+1)) )
  349. 7 CONTINUE
  350. SAWNAN2 = SAWNAN2 .OR. SISNAN( MAX2 )
  351. IF( FORCER .OR.
  352. $ (MAX2.LE.GROWTHBOUND .AND. .NOT.SAWNAN2 ) ) THEN
  353. SIGMA = RSIGMA
  354. SHIFT = SRIGHT
  355. GOTO 100
  356. ENDIF
  357. * If we are at this point, both shifts led to too much element growth
  358. * Record the better of the two shifts (provided it didn't lead to NaN)
  359. IF(SAWNAN1.AND.SAWNAN2) THEN
  360. * both MAX1 and MAX2 are NaN
  361. GOTO 50
  362. ELSE
  363. IF( .NOT.SAWNAN1 ) THEN
  364. INDX = 1
  365. IF(MAX1.LE.SMLGROWTH) THEN
  366. SMLGROWTH = MAX1
  367. BESTSHIFT = LSIGMA
  368. ENDIF
  369. ENDIF
  370. IF( .NOT.SAWNAN2 ) THEN
  371. IF(SAWNAN1 .OR. MAX2.LE.MAX1) INDX = 2
  372. IF(MAX2.LE.SMLGROWTH) THEN
  373. SMLGROWTH = MAX2
  374. BESTSHIFT = RSIGMA
  375. ENDIF
  376. ENDIF
  377. ENDIF
  378. * If we are here, both the left and the right shift led to
  379. * element growth. If the element growth is moderate, then
  380. * we may still accept the representation, if it passes a
  381. * refined test for RRR. This test supposes that no NaN occurred.
  382. * Moreover, we use the refined RRR test only for isolated clusters.
  383. IF((CLWDTH.LT.MINGAP/REAL(128)) .AND.
  384. $ (MIN(MAX1,MAX2).LT.FAIL2)
  385. $ .AND.(.NOT.SAWNAN1).AND.(.NOT.SAWNAN2)) THEN
  386. DORRR1 = .TRUE.
  387. ELSE
  388. DORRR1 = .FALSE.
  389. ENDIF
  390. TRYRRR1 = .TRUE.
  391. IF( TRYRRR1 .AND. DORRR1 ) THEN
  392. IF(INDX.EQ.1) THEN
  393. TMP = ABS( DPLUS( N ) )
  394. ZNM2 = ONE
  395. PROD = ONE
  396. OLDP = ONE
  397. DO 15 I = N-1, 1, -1
  398. IF( PROD .LE. EPS ) THEN
  399. PROD =
  400. $ ((DPLUS(I+1)*WORK(N+I+1))/(DPLUS(I)*WORK(N+I)))*OLDP
  401. ELSE
  402. PROD = PROD*ABS(WORK(N+I))
  403. END IF
  404. OLDP = PROD
  405. ZNM2 = ZNM2 + PROD**2
  406. TMP = MAX( TMP, ABS( DPLUS( I ) * PROD ))
  407. 15 CONTINUE
  408. RRR1 = TMP/( SPDIAM * SQRT( ZNM2 ) )
  409. IF (RRR1.LE.MAXGROWTH2) THEN
  410. SIGMA = LSIGMA
  411. SHIFT = SLEFT
  412. GOTO 100
  413. ENDIF
  414. ELSE IF(INDX.EQ.2) THEN
  415. TMP = ABS( WORK( N ) )
  416. ZNM2 = ONE
  417. PROD = ONE
  418. OLDP = ONE
  419. DO 16 I = N-1, 1, -1
  420. IF( PROD .LE. EPS ) THEN
  421. PROD = ((WORK(I+1)*LPLUS(I+1))/(WORK(I)*LPLUS(I)))*OLDP
  422. ELSE
  423. PROD = PROD*ABS(LPLUS(I))
  424. END IF
  425. OLDP = PROD
  426. ZNM2 = ZNM2 + PROD**2
  427. TMP = MAX( TMP, ABS( WORK( I ) * PROD ))
  428. 16 CONTINUE
  429. RRR2 = TMP/( SPDIAM * SQRT( ZNM2 ) )
  430. IF (RRR2.LE.MAXGROWTH2) THEN
  431. SIGMA = RSIGMA
  432. SHIFT = SRIGHT
  433. GOTO 100
  434. ENDIF
  435. END IF
  436. ENDIF
  437. 50 CONTINUE
  438. IF (KTRY.LT.KTRYMAX) THEN
  439. * If we are here, both shifts failed also the RRR test.
  440. * Back off to the outside
  441. LSIGMA = MAX( LSIGMA - LDELTA,
  442. $ LSIGMA - LDMAX)
  443. RSIGMA = MIN( RSIGMA + RDELTA,
  444. $ RSIGMA + RDMAX )
  445. LDELTA = TWO * LDELTA
  446. RDELTA = TWO * RDELTA
  447. KTRY = KTRY + 1
  448. GOTO 5
  449. ELSE
  450. * None of the representations investigated satisfied our
  451. * criteria. Take the best one we found.
  452. IF((SMLGROWTH.LT.FAIL).OR.NOFAIL) THEN
  453. LSIGMA = BESTSHIFT
  454. RSIGMA = BESTSHIFT
  455. FORCER = .TRUE.
  456. GOTO 5
  457. ELSE
  458. INFO = 1
  459. RETURN
  460. ENDIF
  461. END IF
  462. 100 CONTINUE
  463. IF (SHIFT.EQ.SLEFT) THEN
  464. ELSEIF (SHIFT.EQ.SRIGHT) THEN
  465. * store new L and D back into DPLUS, LPLUS
  466. CALL SCOPY( N, WORK, 1, DPLUS, 1 )
  467. CALL SCOPY( N-1, WORK(N+1), 1, LPLUS, 1 )
  468. ENDIF
  469. RETURN
  470. *
  471. * End of SLARRF
  472. *
  473. END