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.

zlar1v.f 15 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485
  1. *> \brief \b ZLAR1V computes the (scaled) r-th column of the inverse of the submatrix in rows b1 through bn of the tridiagonal matrix LDLT - λI.
  2. *
  3. * =========== DOCUMENTATION ===========
  4. *
  5. * Online html documentation available at
  6. * http://www.netlib.org/lapack/explore-html/
  7. *
  8. *> \htmlonly
  9. *> Download ZLAR1V + dependencies
  10. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlar1v.f">
  11. *> [TGZ]</a>
  12. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlar1v.f">
  13. *> [ZIP]</a>
  14. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlar1v.f">
  15. *> [TXT]</a>
  16. *> \endhtmlonly
  17. *
  18. * Definition:
  19. * ===========
  20. *
  21. * SUBROUTINE ZLAR1V( N, B1, BN, LAMBDA, D, L, LD, LLD,
  22. * PIVMIN, GAPTOL, Z, WANTNC, NEGCNT, ZTZ, MINGMA,
  23. * R, ISUPPZ, NRMINV, RESID, RQCORR, WORK )
  24. *
  25. * .. Scalar Arguments ..
  26. * LOGICAL WANTNC
  27. * INTEGER B1, BN, N, NEGCNT, R
  28. * DOUBLE PRECISION GAPTOL, LAMBDA, MINGMA, NRMINV, PIVMIN, RESID,
  29. * $ RQCORR, ZTZ
  30. * ..
  31. * .. Array Arguments ..
  32. * INTEGER ISUPPZ( * )
  33. * DOUBLE PRECISION D( * ), L( * ), LD( * ), LLD( * ),
  34. * $ WORK( * )
  35. * COMPLEX*16 Z( * )
  36. * ..
  37. *
  38. *
  39. *> \par Purpose:
  40. * =============
  41. *>
  42. *> \verbatim
  43. *>
  44. *> ZLAR1V computes the (scaled) r-th column of the inverse of
  45. *> the sumbmatrix in rows B1 through BN of the tridiagonal matrix
  46. *> L D L**T - sigma I. When sigma is close to an eigenvalue, the
  47. *> computed vector is an accurate eigenvector. Usually, r corresponds
  48. *> to the index where the eigenvector is largest in magnitude.
  49. *> The following steps accomplish this computation :
  50. *> (a) Stationary qd transform, L D L**T - sigma I = L(+) D(+) L(+)**T,
  51. *> (b) Progressive qd transform, L D L**T - sigma I = U(-) D(-) U(-)**T,
  52. *> (c) Computation of the diagonal elements of the inverse of
  53. *> L D L**T - sigma I by combining the above transforms, and choosing
  54. *> r as the index where the diagonal of the inverse is (one of the)
  55. *> largest in magnitude.
  56. *> (d) Computation of the (scaled) r-th column of the inverse using the
  57. *> twisted factorization obtained by combining the top part of the
  58. *> the stationary and the bottom part of the progressive transform.
  59. *> \endverbatim
  60. *
  61. * Arguments:
  62. * ==========
  63. *
  64. *> \param[in] N
  65. *> \verbatim
  66. *> N is INTEGER
  67. *> The order of the matrix L D L**T.
  68. *> \endverbatim
  69. *>
  70. *> \param[in] B1
  71. *> \verbatim
  72. *> B1 is INTEGER
  73. *> First index of the submatrix of L D L**T.
  74. *> \endverbatim
  75. *>
  76. *> \param[in] BN
  77. *> \verbatim
  78. *> BN is INTEGER
  79. *> Last index of the submatrix of L D L**T.
  80. *> \endverbatim
  81. *>
  82. *> \param[in] LAMBDA
  83. *> \verbatim
  84. *> LAMBDA is DOUBLE PRECISION
  85. *> The shift. In order to compute an accurate eigenvector,
  86. *> LAMBDA should be a good approximation to an eigenvalue
  87. *> of L D L**T.
  88. *> \endverbatim
  89. *>
  90. *> \param[in] L
  91. *> \verbatim
  92. *> L is DOUBLE PRECISION array, dimension (N-1)
  93. *> The (n-1) subdiagonal elements of the unit bidiagonal matrix
  94. *> L, in elements 1 to N-1.
  95. *> \endverbatim
  96. *>
  97. *> \param[in] D
  98. *> \verbatim
  99. *> D is DOUBLE PRECISION array, dimension (N)
  100. *> The n diagonal elements of the diagonal matrix D.
  101. *> \endverbatim
  102. *>
  103. *> \param[in] LD
  104. *> \verbatim
  105. *> LD is DOUBLE PRECISION array, dimension (N-1)
  106. *> The n-1 elements L(i)*D(i).
  107. *> \endverbatim
  108. *>
  109. *> \param[in] LLD
  110. *> \verbatim
  111. *> LLD is DOUBLE PRECISION array, dimension (N-1)
  112. *> The n-1 elements L(i)*L(i)*D(i).
  113. *> \endverbatim
  114. *>
  115. *> \param[in] PIVMIN
  116. *> \verbatim
  117. *> PIVMIN is DOUBLE PRECISION
  118. *> The minimum pivot in the Sturm sequence.
  119. *> \endverbatim
  120. *>
  121. *> \param[in] GAPTOL
  122. *> \verbatim
  123. *> GAPTOL is DOUBLE PRECISION
  124. *> Tolerance that indicates when eigenvector entries are negligible
  125. *> w.r.t. their contribution to the residual.
  126. *> \endverbatim
  127. *>
  128. *> \param[in,out] Z
  129. *> \verbatim
  130. *> Z is COMPLEX*16 array, dimension (N)
  131. *> On input, all entries of Z must be set to 0.
  132. *> On output, Z contains the (scaled) r-th column of the
  133. *> inverse. The scaling is such that Z(R) equals 1.
  134. *> \endverbatim
  135. *>
  136. *> \param[in] WANTNC
  137. *> \verbatim
  138. *> WANTNC is LOGICAL
  139. *> Specifies whether NEGCNT has to be computed.
  140. *> \endverbatim
  141. *>
  142. *> \param[out] NEGCNT
  143. *> \verbatim
  144. *> NEGCNT is INTEGER
  145. *> If WANTNC is .TRUE. then NEGCNT = the number of pivots < pivmin
  146. *> in the matrix factorization L D L**T, and NEGCNT = -1 otherwise.
  147. *> \endverbatim
  148. *>
  149. *> \param[out] ZTZ
  150. *> \verbatim
  151. *> ZTZ is DOUBLE PRECISION
  152. *> The square of the 2-norm of Z.
  153. *> \endverbatim
  154. *>
  155. *> \param[out] MINGMA
  156. *> \verbatim
  157. *> MINGMA is DOUBLE PRECISION
  158. *> The reciprocal of the largest (in magnitude) diagonal
  159. *> element of the inverse of L D L**T - sigma I.
  160. *> \endverbatim
  161. *>
  162. *> \param[in,out] R
  163. *> \verbatim
  164. *> R is INTEGER
  165. *> The twist index for the twisted factorization used to
  166. *> compute Z.
  167. *> On input, 0 <= R <= N. If R is input as 0, R is set to
  168. *> the index where (L D L**T - sigma I)^{-1} is largest
  169. *> in magnitude. If 1 <= R <= N, R is unchanged.
  170. *> On output, R contains the twist index used to compute Z.
  171. *> Ideally, R designates the position of the maximum entry in the
  172. *> eigenvector.
  173. *> \endverbatim
  174. *>
  175. *> \param[out] ISUPPZ
  176. *> \verbatim
  177. *> ISUPPZ is INTEGER array, dimension (2)
  178. *> The support of the vector in Z, i.e., the vector Z is
  179. *> nonzero only in elements ISUPPZ(1) through ISUPPZ( 2 ).
  180. *> \endverbatim
  181. *>
  182. *> \param[out] NRMINV
  183. *> \verbatim
  184. *> NRMINV is DOUBLE PRECISION
  185. *> NRMINV = 1/SQRT( ZTZ )
  186. *> \endverbatim
  187. *>
  188. *> \param[out] RESID
  189. *> \verbatim
  190. *> RESID is DOUBLE PRECISION
  191. *> The residual of the FP vector.
  192. *> RESID = ABS( MINGMA )/SQRT( ZTZ )
  193. *> \endverbatim
  194. *>
  195. *> \param[out] RQCORR
  196. *> \verbatim
  197. *> RQCORR is DOUBLE PRECISION
  198. *> The Rayleigh Quotient correction to LAMBDA.
  199. *> RQCORR = MINGMA*TMP
  200. *> \endverbatim
  201. *>
  202. *> \param[out] WORK
  203. *> \verbatim
  204. *> WORK is DOUBLE PRECISION array, dimension (4*N)
  205. *> \endverbatim
  206. *
  207. * Authors:
  208. * ========
  209. *
  210. *> \author Univ. of Tennessee
  211. *> \author Univ. of California Berkeley
  212. *> \author Univ. of Colorado Denver
  213. *> \author NAG Ltd.
  214. *
  215. *> \ingroup complex16OTHERauxiliary
  216. *
  217. *> \par Contributors:
  218. * ==================
  219. *>
  220. *> Beresford Parlett, University of California, Berkeley, USA \n
  221. *> Jim Demmel, University of California, Berkeley, USA \n
  222. *> Inderjit Dhillon, University of Texas, Austin, USA \n
  223. *> Osni Marques, LBNL/NERSC, USA \n
  224. *> Christof Voemel, University of California, Berkeley, USA
  225. *
  226. * =====================================================================
  227. SUBROUTINE ZLAR1V( N, B1, BN, LAMBDA, D, L, LD, LLD,
  228. $ PIVMIN, GAPTOL, Z, WANTNC, NEGCNT, ZTZ, MINGMA,
  229. $ R, ISUPPZ, NRMINV, RESID, RQCORR, WORK )
  230. *
  231. * -- LAPACK auxiliary routine --
  232. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  233. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  234. *
  235. * .. Scalar Arguments ..
  236. LOGICAL WANTNC
  237. INTEGER B1, BN, N, NEGCNT, R
  238. DOUBLE PRECISION GAPTOL, LAMBDA, MINGMA, NRMINV, PIVMIN, RESID,
  239. $ RQCORR, ZTZ
  240. * ..
  241. * .. Array Arguments ..
  242. INTEGER ISUPPZ( * )
  243. DOUBLE PRECISION D( * ), L( * ), LD( * ), LLD( * ),
  244. $ WORK( * )
  245. COMPLEX*16 Z( * )
  246. * ..
  247. *
  248. * =====================================================================
  249. *
  250. * .. Parameters ..
  251. DOUBLE PRECISION ZERO, ONE
  252. PARAMETER ( ZERO = 0.0D0, ONE = 1.0D0 )
  253. COMPLEX*16 CONE
  254. PARAMETER ( CONE = ( 1.0D0, 0.0D0 ) )
  255. * ..
  256. * .. Local Scalars ..
  257. LOGICAL SAWNAN1, SAWNAN2
  258. INTEGER I, INDLPL, INDP, INDS, INDUMN, NEG1, NEG2, R1,
  259. $ R2
  260. DOUBLE PRECISION DMINUS, DPLUS, EPS, S, TMP
  261. * ..
  262. * .. External Functions ..
  263. LOGICAL DISNAN
  264. DOUBLE PRECISION DLAMCH
  265. EXTERNAL DISNAN, DLAMCH
  266. * ..
  267. * .. Intrinsic Functions ..
  268. INTRINSIC ABS, DBLE
  269. * ..
  270. * .. Executable Statements ..
  271. *
  272. EPS = DLAMCH( 'Precision' )
  273. IF( R.EQ.0 ) THEN
  274. R1 = B1
  275. R2 = BN
  276. ELSE
  277. R1 = R
  278. R2 = R
  279. END IF
  280. * Storage for LPLUS
  281. INDLPL = 0
  282. * Storage for UMINUS
  283. INDUMN = N
  284. INDS = 2*N + 1
  285. INDP = 3*N + 1
  286. IF( B1.EQ.1 ) THEN
  287. WORK( INDS ) = ZERO
  288. ELSE
  289. WORK( INDS+B1-1 ) = LLD( B1-1 )
  290. END IF
  291. *
  292. * Compute the stationary transform (using the differential form)
  293. * until the index R2.
  294. *
  295. SAWNAN1 = .FALSE.
  296. NEG1 = 0
  297. S = WORK( INDS+B1-1 ) - LAMBDA
  298. DO 50 I = B1, R1 - 1
  299. DPLUS = D( I ) + S
  300. WORK( INDLPL+I ) = LD( I ) / DPLUS
  301. IF(DPLUS.LT.ZERO) NEG1 = NEG1 + 1
  302. WORK( INDS+I ) = S*WORK( INDLPL+I )*L( I )
  303. S = WORK( INDS+I ) - LAMBDA
  304. 50 CONTINUE
  305. SAWNAN1 = DISNAN( S )
  306. IF( SAWNAN1 ) GOTO 60
  307. DO 51 I = R1, R2 - 1
  308. DPLUS = D( I ) + S
  309. WORK( INDLPL+I ) = LD( I ) / DPLUS
  310. WORK( INDS+I ) = S*WORK( INDLPL+I )*L( I )
  311. S = WORK( INDS+I ) - LAMBDA
  312. 51 CONTINUE
  313. SAWNAN1 = DISNAN( S )
  314. *
  315. 60 CONTINUE
  316. IF( SAWNAN1 ) THEN
  317. * Runs a slower version of the above loop if a NaN is detected
  318. NEG1 = 0
  319. S = WORK( INDS+B1-1 ) - LAMBDA
  320. DO 70 I = B1, R1 - 1
  321. DPLUS = D( I ) + S
  322. IF(ABS(DPLUS).LT.PIVMIN) DPLUS = -PIVMIN
  323. WORK( INDLPL+I ) = LD( I ) / DPLUS
  324. IF(DPLUS.LT.ZERO) NEG1 = NEG1 + 1
  325. WORK( INDS+I ) = S*WORK( INDLPL+I )*L( I )
  326. IF( WORK( INDLPL+I ).EQ.ZERO )
  327. $ WORK( INDS+I ) = LLD( I )
  328. S = WORK( INDS+I ) - LAMBDA
  329. 70 CONTINUE
  330. DO 71 I = R1, R2 - 1
  331. DPLUS = D( I ) + S
  332. IF(ABS(DPLUS).LT.PIVMIN) DPLUS = -PIVMIN
  333. WORK( INDLPL+I ) = LD( I ) / DPLUS
  334. WORK( INDS+I ) = S*WORK( INDLPL+I )*L( I )
  335. IF( WORK( INDLPL+I ).EQ.ZERO )
  336. $ WORK( INDS+I ) = LLD( I )
  337. S = WORK( INDS+I ) - LAMBDA
  338. 71 CONTINUE
  339. END IF
  340. *
  341. * Compute the progressive transform (using the differential form)
  342. * until the index R1
  343. *
  344. SAWNAN2 = .FALSE.
  345. NEG2 = 0
  346. WORK( INDP+BN-1 ) = D( BN ) - LAMBDA
  347. DO 80 I = BN - 1, R1, -1
  348. DMINUS = LLD( I ) + WORK( INDP+I )
  349. TMP = D( I ) / DMINUS
  350. IF(DMINUS.LT.ZERO) NEG2 = NEG2 + 1
  351. WORK( INDUMN+I ) = L( I )*TMP
  352. WORK( INDP+I-1 ) = WORK( INDP+I )*TMP - LAMBDA
  353. 80 CONTINUE
  354. TMP = WORK( INDP+R1-1 )
  355. SAWNAN2 = DISNAN( TMP )
  356. IF( SAWNAN2 ) THEN
  357. * Runs a slower version of the above loop if a NaN is detected
  358. NEG2 = 0
  359. DO 100 I = BN-1, R1, -1
  360. DMINUS = LLD( I ) + WORK( INDP+I )
  361. IF(ABS(DMINUS).LT.PIVMIN) DMINUS = -PIVMIN
  362. TMP = D( I ) / DMINUS
  363. IF(DMINUS.LT.ZERO) NEG2 = NEG2 + 1
  364. WORK( INDUMN+I ) = L( I )*TMP
  365. WORK( INDP+I-1 ) = WORK( INDP+I )*TMP - LAMBDA
  366. IF( TMP.EQ.ZERO )
  367. $ WORK( INDP+I-1 ) = D( I ) - LAMBDA
  368. 100 CONTINUE
  369. END IF
  370. *
  371. * Find the index (from R1 to R2) of the largest (in magnitude)
  372. * diagonal element of the inverse
  373. *
  374. MINGMA = WORK( INDS+R1-1 ) + WORK( INDP+R1-1 )
  375. IF( MINGMA.LT.ZERO ) NEG1 = NEG1 + 1
  376. IF( WANTNC ) THEN
  377. NEGCNT = NEG1 + NEG2
  378. ELSE
  379. NEGCNT = -1
  380. ENDIF
  381. IF( ABS(MINGMA).EQ.ZERO )
  382. $ MINGMA = EPS*WORK( INDS+R1-1 )
  383. R = R1
  384. DO 110 I = R1, R2 - 1
  385. TMP = WORK( INDS+I ) + WORK( INDP+I )
  386. IF( TMP.EQ.ZERO )
  387. $ TMP = EPS*WORK( INDS+I )
  388. IF( ABS( TMP ).LE.ABS( MINGMA ) ) THEN
  389. MINGMA = TMP
  390. R = I + 1
  391. END IF
  392. 110 CONTINUE
  393. *
  394. * Compute the FP vector: solve N^T v = e_r
  395. *
  396. ISUPPZ( 1 ) = B1
  397. ISUPPZ( 2 ) = BN
  398. Z( R ) = CONE
  399. ZTZ = ONE
  400. *
  401. * Compute the FP vector upwards from R
  402. *
  403. IF( .NOT.SAWNAN1 .AND. .NOT.SAWNAN2 ) THEN
  404. DO 210 I = R-1, B1, -1
  405. Z( I ) = -( WORK( INDLPL+I )*Z( I+1 ) )
  406. IF( (ABS(Z(I))+ABS(Z(I+1)))* ABS(LD(I)).LT.GAPTOL )
  407. $ THEN
  408. Z( I ) = ZERO
  409. ISUPPZ( 1 ) = I + 1
  410. GOTO 220
  411. ENDIF
  412. ZTZ = ZTZ + DBLE( Z( I )*Z( I ) )
  413. 210 CONTINUE
  414. 220 CONTINUE
  415. ELSE
  416. * Run slower loop if NaN occurred.
  417. DO 230 I = R - 1, B1, -1
  418. IF( Z( I+1 ).EQ.ZERO ) THEN
  419. Z( I ) = -( LD( I+1 ) / LD( I ) )*Z( I+2 )
  420. ELSE
  421. Z( I ) = -( WORK( INDLPL+I )*Z( I+1 ) )
  422. END IF
  423. IF( (ABS(Z(I))+ABS(Z(I+1)))* ABS(LD(I)).LT.GAPTOL )
  424. $ THEN
  425. Z( I ) = ZERO
  426. ISUPPZ( 1 ) = I + 1
  427. GO TO 240
  428. END IF
  429. ZTZ = ZTZ + DBLE( Z( I )*Z( I ) )
  430. 230 CONTINUE
  431. 240 CONTINUE
  432. ENDIF
  433. * Compute the FP vector downwards from R in blocks of size BLKSIZ
  434. IF( .NOT.SAWNAN1 .AND. .NOT.SAWNAN2 ) THEN
  435. DO 250 I = R, BN-1
  436. Z( I+1 ) = -( WORK( INDUMN+I )*Z( I ) )
  437. IF( (ABS(Z(I))+ABS(Z(I+1)))* ABS(LD(I)).LT.GAPTOL )
  438. $ THEN
  439. Z( I+1 ) = ZERO
  440. ISUPPZ( 2 ) = I
  441. GO TO 260
  442. END IF
  443. ZTZ = ZTZ + DBLE( Z( I+1 )*Z( I+1 ) )
  444. 250 CONTINUE
  445. 260 CONTINUE
  446. ELSE
  447. * Run slower loop if NaN occurred.
  448. DO 270 I = R, BN - 1
  449. IF( Z( I ).EQ.ZERO ) THEN
  450. Z( I+1 ) = -( LD( I-1 ) / LD( I ) )*Z( I-1 )
  451. ELSE
  452. Z( I+1 ) = -( WORK( INDUMN+I )*Z( I ) )
  453. END IF
  454. IF( (ABS(Z(I))+ABS(Z(I+1)))* ABS(LD(I)).LT.GAPTOL )
  455. $ THEN
  456. Z( I+1 ) = ZERO
  457. ISUPPZ( 2 ) = I
  458. GO TO 280
  459. END IF
  460. ZTZ = ZTZ + DBLE( Z( I+1 )*Z( I+1 ) )
  461. 270 CONTINUE
  462. 280 CONTINUE
  463. END IF
  464. *
  465. * Compute quantities for convergence test
  466. *
  467. TMP = ONE / ZTZ
  468. NRMINV = SQRT( TMP )
  469. RESID = ABS( MINGMA )*NRMINV
  470. RQCORR = MINGMA*TMP
  471. *
  472. *
  473. RETURN
  474. *
  475. * End of ZLAR1V
  476. *
  477. END