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.

dlarrk.f 6.7 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253
  1. *> \brief \b DLARRK computes one eigenvalue of a symmetric tridiagonal matrix T to suitable accuracy.
  2. *
  3. * =========== DOCUMENTATION ===========
  4. *
  5. * Online html documentation available at
  6. * http://www.netlib.org/lapack/explore-html/
  7. *
  8. *> \htmlonly
  9. *> Download DLARRK + dependencies
  10. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlarrk.f">
  11. *> [TGZ]</a>
  12. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlarrk.f">
  13. *> [ZIP]</a>
  14. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlarrk.f">
  15. *> [TXT]</a>
  16. *> \endhtmlonly
  17. *
  18. * Definition:
  19. * ===========
  20. *
  21. * SUBROUTINE DLARRK( N, IW, GL, GU,
  22. * D, E2, PIVMIN, RELTOL, W, WERR, INFO)
  23. *
  24. * .. Scalar Arguments ..
  25. * INTEGER INFO, IW, N
  26. * DOUBLE PRECISION PIVMIN, RELTOL, GL, GU, W, WERR
  27. * ..
  28. * .. Array Arguments ..
  29. * DOUBLE PRECISION D( * ), E2( * )
  30. * ..
  31. *
  32. *
  33. *> \par Purpose:
  34. * =============
  35. *>
  36. *> \verbatim
  37. *>
  38. *> DLARRK computes one eigenvalue of a symmetric tridiagonal
  39. *> matrix T to suitable accuracy. This is an auxiliary code to be
  40. *> called from DSTEMR.
  41. *>
  42. *> To avoid overflow, the matrix must be scaled so that its
  43. *> largest element is no greater than overflow**(1/2) * underflow**(1/4) in absolute value, and for greatest
  44. *> accuracy, it should not be much smaller than that.
  45. *>
  46. *> See W. Kahan "Accurate Eigenvalues of a Symmetric Tridiagonal
  47. *> Matrix", Report CS41, Computer Science Dept., Stanford
  48. *> University, July 21, 1966.
  49. *> \endverbatim
  50. *
  51. * Arguments:
  52. * ==========
  53. *
  54. *> \param[in] N
  55. *> \verbatim
  56. *> N is INTEGER
  57. *> The order of the tridiagonal matrix T. N >= 0.
  58. *> \endverbatim
  59. *>
  60. *> \param[in] IW
  61. *> \verbatim
  62. *> IW is INTEGER
  63. *> The index of the eigenvalues to be returned.
  64. *> \endverbatim
  65. *>
  66. *> \param[in] GL
  67. *> \verbatim
  68. *> GL is DOUBLE PRECISION
  69. *> \endverbatim
  70. *>
  71. *> \param[in] GU
  72. *> \verbatim
  73. *> GU is DOUBLE PRECISION
  74. *> An upper and a lower bound on the eigenvalue.
  75. *> \endverbatim
  76. *>
  77. *> \param[in] D
  78. *> \verbatim
  79. *> D is DOUBLE PRECISION array, dimension (N)
  80. *> The n diagonal elements of the tridiagonal matrix T.
  81. *> \endverbatim
  82. *>
  83. *> \param[in] E2
  84. *> \verbatim
  85. *> E2 is DOUBLE PRECISION array, dimension (N-1)
  86. *> The (n-1) squared off-diagonal elements of the tridiagonal matrix T.
  87. *> \endverbatim
  88. *>
  89. *> \param[in] PIVMIN
  90. *> \verbatim
  91. *> PIVMIN is DOUBLE PRECISION
  92. *> The minimum pivot allowed in the Sturm sequence for T.
  93. *> \endverbatim
  94. *>
  95. *> \param[in] RELTOL
  96. *> \verbatim
  97. *> RELTOL is DOUBLE PRECISION
  98. *> The minimum relative width of an interval. When an interval
  99. *> is narrower than RELTOL times the larger (in
  100. *> magnitude) endpoint, then it is considered to be
  101. *> sufficiently small, i.e., converged. Note: this should
  102. *> always be at least radix*machine epsilon.
  103. *> \endverbatim
  104. *>
  105. *> \param[out] W
  106. *> \verbatim
  107. *> W is DOUBLE PRECISION
  108. *> \endverbatim
  109. *>
  110. *> \param[out] WERR
  111. *> \verbatim
  112. *> WERR is DOUBLE PRECISION
  113. *> The error bound on the corresponding eigenvalue approximation
  114. *> in W.
  115. *> \endverbatim
  116. *>
  117. *> \param[out] INFO
  118. *> \verbatim
  119. *> INFO is INTEGER
  120. *> = 0: Eigenvalue converged
  121. *> = -1: Eigenvalue did NOT converge
  122. *> \endverbatim
  123. *
  124. *> \par Internal Parameters:
  125. * =========================
  126. *>
  127. *> \verbatim
  128. *> FUDGE DOUBLE PRECISION, default = 2
  129. *> A "fudge factor" to widen the Gershgorin intervals.
  130. *> \endverbatim
  131. *
  132. * Authors:
  133. * ========
  134. *
  135. *> \author Univ. of Tennessee
  136. *> \author Univ. of California Berkeley
  137. *> \author Univ. of Colorado Denver
  138. *> \author NAG Ltd.
  139. *
  140. *> \ingroup OTHERauxiliary
  141. *
  142. * =====================================================================
  143. SUBROUTINE DLARRK( N, IW, GL, GU,
  144. $ D, E2, PIVMIN, RELTOL, W, WERR, INFO)
  145. *
  146. * -- LAPACK auxiliary routine --
  147. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  148. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  149. *
  150. * .. Scalar Arguments ..
  151. INTEGER INFO, IW, N
  152. DOUBLE PRECISION PIVMIN, RELTOL, GL, GU, W, WERR
  153. * ..
  154. * .. Array Arguments ..
  155. DOUBLE PRECISION D( * ), E2( * )
  156. * ..
  157. *
  158. * =====================================================================
  159. *
  160. * .. Parameters ..
  161. DOUBLE PRECISION FUDGE, HALF, TWO, ZERO
  162. PARAMETER ( HALF = 0.5D0, TWO = 2.0D0,
  163. $ FUDGE = TWO, ZERO = 0.0D0 )
  164. * ..
  165. * .. Local Scalars ..
  166. INTEGER I, IT, ITMAX, NEGCNT
  167. DOUBLE PRECISION ATOLI, EPS, LEFT, MID, RIGHT, RTOLI, TMP1,
  168. $ TMP2, TNORM
  169. * ..
  170. * .. External Functions ..
  171. DOUBLE PRECISION DLAMCH
  172. EXTERNAL DLAMCH
  173. * ..
  174. * .. Intrinsic Functions ..
  175. INTRINSIC ABS, INT, LOG, MAX
  176. * ..
  177. * .. Executable Statements ..
  178. *
  179. * Quick return if possible
  180. *
  181. IF( N.LE.0 ) THEN
  182. INFO = 0
  183. RETURN
  184. END IF
  185. *
  186. * Get machine constants
  187. EPS = DLAMCH( 'P' )
  188. TNORM = MAX( ABS( GL ), ABS( GU ) )
  189. RTOLI = RELTOL
  190. ATOLI = FUDGE*TWO*PIVMIN
  191. ITMAX = INT( ( LOG( TNORM+PIVMIN )-LOG( PIVMIN ) ) /
  192. $ LOG( TWO ) ) + 2
  193. INFO = -1
  194. LEFT = GL - FUDGE*TNORM*EPS*N - FUDGE*TWO*PIVMIN
  195. RIGHT = GU + FUDGE*TNORM*EPS*N + FUDGE*TWO*PIVMIN
  196. IT = 0
  197. 10 CONTINUE
  198. *
  199. * Check if interval converged or maximum number of iterations reached
  200. *
  201. TMP1 = ABS( RIGHT - LEFT )
  202. TMP2 = MAX( ABS(RIGHT), ABS(LEFT) )
  203. IF( TMP1.LT.MAX( ATOLI, PIVMIN, RTOLI*TMP2 ) ) THEN
  204. INFO = 0
  205. GOTO 30
  206. ENDIF
  207. IF(IT.GT.ITMAX)
  208. $ GOTO 30
  209. *
  210. * Count number of negative pivots for mid-point
  211. *
  212. IT = IT + 1
  213. MID = HALF * (LEFT + RIGHT)
  214. NEGCNT = 0
  215. TMP1 = D( 1 ) - MID
  216. IF( ABS( TMP1 ).LT.PIVMIN )
  217. $ TMP1 = -PIVMIN
  218. IF( TMP1.LE.ZERO )
  219. $ NEGCNT = NEGCNT + 1
  220. *
  221. DO 20 I = 2, N
  222. TMP1 = D( I ) - E2( I-1 ) / TMP1 - MID
  223. IF( ABS( TMP1 ).LT.PIVMIN )
  224. $ TMP1 = -PIVMIN
  225. IF( TMP1.LE.ZERO )
  226. $ NEGCNT = NEGCNT + 1
  227. 20 CONTINUE
  228. IF(NEGCNT.GE.IW) THEN
  229. RIGHT = MID
  230. ELSE
  231. LEFT = MID
  232. ENDIF
  233. GOTO 10
  234. 30 CONTINUE
  235. *
  236. * Converged or maximum number of iterations reached
  237. *
  238. W = HALF * (LEFT + RIGHT)
  239. WERR = HALF * ABS( RIGHT - LEFT )
  240. RETURN
  241. *
  242. * End of DLARRK
  243. *
  244. END