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

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495
  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. *> \date June 2016
  178. *
  179. *> \ingroup OTHERauxiliary
  180. *
  181. *> \par Contributors:
  182. * ==================
  183. *>
  184. *> Beresford Parlett, University of California, Berkeley, USA \n
  185. *> Jim Demmel, University of California, Berkeley, USA \n
  186. *> Inderjit Dhillon, University of Texas, Austin, USA \n
  187. *> Osni Marques, LBNL/NERSC, USA \n
  188. *> Christof Voemel, University of California, Berkeley, USA
  189. *
  190. * =====================================================================
  191. SUBROUTINE SLARRF( N, D, L, LD, CLSTRT, CLEND,
  192. $ W, WGAP, WERR,
  193. $ SPDIAM, CLGAPL, CLGAPR, PIVMIN, SIGMA,
  194. $ DPLUS, LPLUS, WORK, INFO )
  195. *
  196. * -- LAPACK auxiliary routine (version 3.7.1) --
  197. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  198. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  199. * June 2016
  200. *
  201. * .. Scalar Arguments ..
  202. INTEGER CLSTRT, CLEND, INFO, N
  203. REAL CLGAPL, CLGAPR, PIVMIN, SIGMA, SPDIAM
  204. * ..
  205. * .. Array Arguments ..
  206. REAL D( * ), DPLUS( * ), L( * ), LD( * ),
  207. $ LPLUS( * ), W( * ), WGAP( * ), WERR( * ), WORK( * )
  208. * ..
  209. *
  210. * =====================================================================
  211. *
  212. * .. Parameters ..
  213. REAL MAXGROWTH1, MAXGROWTH2, ONE, QUART, TWO
  214. PARAMETER ( ONE = 1.0E0, TWO = 2.0E0,
  215. $ QUART = 0.25E0,
  216. $ MAXGROWTH1 = 8.E0,
  217. $ MAXGROWTH2 = 8.E0 )
  218. * ..
  219. * .. Local Scalars ..
  220. LOGICAL DORRR1, FORCER, NOFAIL, SAWNAN1, SAWNAN2, TRYRRR1
  221. INTEGER I, INDX, KTRY, KTRYMAX, SLEFT, SRIGHT, SHIFT
  222. PARAMETER ( KTRYMAX = 1, SLEFT = 1, SRIGHT = 2 )
  223. REAL AVGAP, BESTSHIFT, CLWDTH, EPS, FACT, FAIL,
  224. $ FAIL2, GROWTHBOUND, LDELTA, LDMAX, LSIGMA,
  225. $ MAX1, MAX2, MINGAP, OLDP, PROD, RDELTA, RDMAX,
  226. $ RRR1, RRR2, RSIGMA, S, SMLGROWTH, TMP, ZNM2
  227. * ..
  228. * .. External Functions ..
  229. LOGICAL SISNAN
  230. REAL SLAMCH
  231. EXTERNAL SISNAN, SLAMCH
  232. * ..
  233. * .. External Subroutines ..
  234. EXTERNAL SCOPY
  235. * ..
  236. * .. Intrinsic Functions ..
  237. INTRINSIC ABS
  238. * ..
  239. * .. Executable Statements ..
  240. *
  241. INFO = 0
  242. *
  243. * Quick return if possible
  244. *
  245. IF( N.LE.0 ) THEN
  246. RETURN
  247. END IF
  248. *
  249. FACT = REAL(2**KTRYMAX)
  250. EPS = SLAMCH( 'Precision' )
  251. SHIFT = 0
  252. FORCER = .FALSE.
  253. * Note that we cannot guarantee that for any of the shifts tried,
  254. * the factorization has a small or even moderate element growth.
  255. * There could be Ritz values at both ends of the cluster and despite
  256. * backing off, there are examples where all factorizations tried
  257. * (in IEEE mode, allowing zero pivots & infinities) have INFINITE
  258. * element growth.
  259. * For this reason, we should use PIVMIN in this subroutine so that at
  260. * least the L D L^T factorization exists. It can be checked afterwards
  261. * whether the element growth caused bad residuals/orthogonality.
  262. * Decide whether the code should accept the best among all
  263. * representations despite large element growth or signal INFO=1
  264. * Setting NOFAIL to .FALSE. for quick fix for bug 113
  265. NOFAIL = .FALSE.
  266. *
  267. * Compute the average gap length of the cluster
  268. CLWDTH = ABS(W(CLEND)-W(CLSTRT)) + WERR(CLEND) + WERR(CLSTRT)
  269. AVGAP = CLWDTH / REAL(CLEND-CLSTRT)
  270. MINGAP = MIN(CLGAPL, CLGAPR)
  271. * Initial values for shifts to both ends of cluster
  272. LSIGMA = MIN(W( CLSTRT ),W( CLEND )) - WERR( CLSTRT )
  273. RSIGMA = MAX(W( CLSTRT ),W( CLEND )) + WERR( CLEND )
  274. * Use a small fudge to make sure that we really shift to the outside
  275. LSIGMA = LSIGMA - ABS(LSIGMA)* TWO * EPS
  276. RSIGMA = RSIGMA + ABS(RSIGMA)* TWO * EPS
  277. * Compute upper bounds for how much to back off the initial shifts
  278. LDMAX = QUART * MINGAP + TWO * PIVMIN
  279. RDMAX = QUART * MINGAP + TWO * PIVMIN
  280. LDELTA = MAX(AVGAP,WGAP( CLSTRT ))/FACT
  281. RDELTA = MAX(AVGAP,WGAP( CLEND-1 ))/FACT
  282. *
  283. * Initialize the record of the best representation found
  284. *
  285. S = SLAMCH( 'S' )
  286. SMLGROWTH = ONE / S
  287. FAIL = REAL(N-1)*MINGAP/(SPDIAM*EPS)
  288. FAIL2 = REAL(N-1)*MINGAP/(SPDIAM*SQRT(EPS))
  289. BESTSHIFT = LSIGMA
  290. *
  291. * while (KTRY <= KTRYMAX)
  292. KTRY = 0
  293. GROWTHBOUND = MAXGROWTH1*SPDIAM
  294. 5 CONTINUE
  295. SAWNAN1 = .FALSE.
  296. SAWNAN2 = .FALSE.
  297. * Ensure that we do not back off too much of the initial shifts
  298. LDELTA = MIN(LDMAX,LDELTA)
  299. RDELTA = MIN(RDMAX,RDELTA)
  300. * Compute the element growth when shifting to both ends of the cluster
  301. * accept the shift if there is no element growth at one of the two ends
  302. * Left end
  303. S = -LSIGMA
  304. DPLUS( 1 ) = D( 1 ) + S
  305. IF(ABS(DPLUS(1)).LT.PIVMIN) THEN
  306. DPLUS(1) = -PIVMIN
  307. * Need to set SAWNAN1 because refined RRR test should not be used
  308. * in this case
  309. SAWNAN1 = .TRUE.
  310. ENDIF
  311. MAX1 = ABS( DPLUS( 1 ) )
  312. DO 6 I = 1, N - 1
  313. LPLUS( I ) = LD( I ) / DPLUS( I )
  314. S = S*LPLUS( I )*L( I ) - LSIGMA
  315. DPLUS( I+1 ) = D( I+1 ) + S
  316. IF(ABS(DPLUS(I+1)).LT.PIVMIN) THEN
  317. DPLUS(I+1) = -PIVMIN
  318. * Need to set SAWNAN1 because refined RRR test should not be used
  319. * in this case
  320. SAWNAN1 = .TRUE.
  321. ENDIF
  322. MAX1 = MAX( MAX1,ABS(DPLUS(I+1)) )
  323. 6 CONTINUE
  324. SAWNAN1 = SAWNAN1 .OR. SISNAN( MAX1 )
  325. IF( FORCER .OR.
  326. $ (MAX1.LE.GROWTHBOUND .AND. .NOT.SAWNAN1 ) ) THEN
  327. SIGMA = LSIGMA
  328. SHIFT = SLEFT
  329. GOTO 100
  330. ENDIF
  331. * Right end
  332. S = -RSIGMA
  333. WORK( 1 ) = D( 1 ) + S
  334. IF(ABS(WORK(1)).LT.PIVMIN) THEN
  335. WORK(1) = -PIVMIN
  336. * Need to set SAWNAN2 because refined RRR test should not be used
  337. * in this case
  338. SAWNAN2 = .TRUE.
  339. ENDIF
  340. MAX2 = ABS( WORK( 1 ) )
  341. DO 7 I = 1, N - 1
  342. WORK( N+I ) = LD( I ) / WORK( I )
  343. S = S*WORK( N+I )*L( I ) - RSIGMA
  344. WORK( I+1 ) = D( I+1 ) + S
  345. IF(ABS(WORK(I+1)).LT.PIVMIN) THEN
  346. WORK(I+1) = -PIVMIN
  347. * Need to set SAWNAN2 because refined RRR test should not be used
  348. * in this case
  349. SAWNAN2 = .TRUE.
  350. ENDIF
  351. MAX2 = MAX( MAX2,ABS(WORK(I+1)) )
  352. 7 CONTINUE
  353. SAWNAN2 = SAWNAN2 .OR. SISNAN( MAX2 )
  354. IF( FORCER .OR.
  355. $ (MAX2.LE.GROWTHBOUND .AND. .NOT.SAWNAN2 ) ) THEN
  356. SIGMA = RSIGMA
  357. SHIFT = SRIGHT
  358. GOTO 100
  359. ENDIF
  360. * If we are at this point, both shifts led to too much element growth
  361. * Record the better of the two shifts (provided it didn't lead to NaN)
  362. IF(SAWNAN1.AND.SAWNAN2) THEN
  363. * both MAX1 and MAX2 are NaN
  364. GOTO 50
  365. ELSE
  366. IF( .NOT.SAWNAN1 ) THEN
  367. INDX = 1
  368. IF(MAX1.LE.SMLGROWTH) THEN
  369. SMLGROWTH = MAX1
  370. BESTSHIFT = LSIGMA
  371. ENDIF
  372. ENDIF
  373. IF( .NOT.SAWNAN2 ) THEN
  374. IF(SAWNAN1 .OR. MAX2.LE.MAX1) INDX = 2
  375. IF(MAX2.LE.SMLGROWTH) THEN
  376. SMLGROWTH = MAX2
  377. BESTSHIFT = RSIGMA
  378. ENDIF
  379. ENDIF
  380. ENDIF
  381. * If we are here, both the left and the right shift led to
  382. * element growth. If the element growth is moderate, then
  383. * we may still accept the representation, if it passes a
  384. * refined test for RRR. This test supposes that no NaN occurred.
  385. * Moreover, we use the refined RRR test only for isolated clusters.
  386. IF((CLWDTH.LT.MINGAP/REAL(128)) .AND.
  387. $ (MIN(MAX1,MAX2).LT.FAIL2)
  388. $ .AND.(.NOT.SAWNAN1).AND.(.NOT.SAWNAN2)) THEN
  389. DORRR1 = .TRUE.
  390. ELSE
  391. DORRR1 = .FALSE.
  392. ENDIF
  393. TRYRRR1 = .TRUE.
  394. IF( TRYRRR1 .AND. DORRR1 ) THEN
  395. IF(INDX.EQ.1) THEN
  396. TMP = ABS( DPLUS( N ) )
  397. ZNM2 = ONE
  398. PROD = ONE
  399. OLDP = ONE
  400. DO 15 I = N-1, 1, -1
  401. IF( PROD .LE. EPS ) THEN
  402. PROD =
  403. $ ((DPLUS(I+1)*WORK(N+I+1))/(DPLUS(I)*WORK(N+I)))*OLDP
  404. ELSE
  405. PROD = PROD*ABS(WORK(N+I))
  406. END IF
  407. OLDP = PROD
  408. ZNM2 = ZNM2 + PROD**2
  409. TMP = MAX( TMP, ABS( DPLUS( I ) * PROD ))
  410. 15 CONTINUE
  411. RRR1 = TMP/( SPDIAM * SQRT( ZNM2 ) )
  412. IF (RRR1.LE.MAXGROWTH2) THEN
  413. SIGMA = LSIGMA
  414. SHIFT = SLEFT
  415. GOTO 100
  416. ENDIF
  417. ELSE IF(INDX.EQ.2) THEN
  418. TMP = ABS( WORK( N ) )
  419. ZNM2 = ONE
  420. PROD = ONE
  421. OLDP = ONE
  422. DO 16 I = N-1, 1, -1
  423. IF( PROD .LE. EPS ) THEN
  424. PROD = ((WORK(I+1)*LPLUS(I+1))/(WORK(I)*LPLUS(I)))*OLDP
  425. ELSE
  426. PROD = PROD*ABS(LPLUS(I))
  427. END IF
  428. OLDP = PROD
  429. ZNM2 = ZNM2 + PROD**2
  430. TMP = MAX( TMP, ABS( WORK( I ) * PROD ))
  431. 16 CONTINUE
  432. RRR2 = TMP/( SPDIAM * SQRT( ZNM2 ) )
  433. IF (RRR2.LE.MAXGROWTH2) THEN
  434. SIGMA = RSIGMA
  435. SHIFT = SRIGHT
  436. GOTO 100
  437. ENDIF
  438. END IF
  439. ENDIF
  440. 50 CONTINUE
  441. IF (KTRY.LT.KTRYMAX) THEN
  442. * If we are here, both shifts failed also the RRR test.
  443. * Back off to the outside
  444. LSIGMA = MAX( LSIGMA - LDELTA,
  445. $ LSIGMA - LDMAX)
  446. RSIGMA = MIN( RSIGMA + RDELTA,
  447. $ RSIGMA + RDMAX )
  448. LDELTA = TWO * LDELTA
  449. RDELTA = TWO * RDELTA
  450. KTRY = KTRY + 1
  451. GOTO 5
  452. ELSE
  453. * None of the representations investigated satisfied our
  454. * criteria. Take the best one we found.
  455. IF((SMLGROWTH.LT.FAIL).OR.NOFAIL) THEN
  456. LSIGMA = BESTSHIFT
  457. RSIGMA = BESTSHIFT
  458. FORCER = .TRUE.
  459. GOTO 5
  460. ELSE
  461. INFO = 1
  462. RETURN
  463. ENDIF
  464. END IF
  465. 100 CONTINUE
  466. IF (SHIFT.EQ.SLEFT) THEN
  467. ELSEIF (SHIFT.EQ.SRIGHT) THEN
  468. * store new L and D back into DPLUS, LPLUS
  469. CALL SCOPY( N, WORK, 1, DPLUS, 1 )
  470. CALL SCOPY( N-1, WORK(N+1), 1, LPLUS, 1 )
  471. ENDIF
  472. RETURN
  473. *
  474. * End of SLARRF
  475. *
  476. END