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.

dsvdch.f 5.7 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209
  1. *> \brief \b DSVDCH
  2. *
  3. * =========== DOCUMENTATION ===========
  4. *
  5. * Online html documentation available at
  6. * http://www.netlib.org/lapack/explore-html/
  7. *
  8. * Definition:
  9. * ===========
  10. *
  11. * SUBROUTINE DSVDCH( N, S, E, SVD, TOL, INFO )
  12. *
  13. * .. Scalar Arguments ..
  14. * INTEGER INFO, N
  15. * DOUBLE PRECISION TOL
  16. * ..
  17. * .. Array Arguments ..
  18. * DOUBLE PRECISION E( * ), S( * ), SVD( * )
  19. * ..
  20. *
  21. *
  22. *> \par Purpose:
  23. * =============
  24. *>
  25. *> \verbatim
  26. *>
  27. *> DSVDCH checks to see if SVD(1) ,..., SVD(N) are accurate singular
  28. *> values of the bidiagonal matrix B with diagonal entries
  29. *> S(1) ,..., S(N) and superdiagonal entries E(1) ,..., E(N-1)).
  30. *> It does this by expanding each SVD(I) into an interval
  31. *> [SVD(I) * (1-EPS) , SVD(I) * (1+EPS)], merging overlapping intervals
  32. *> if any, and using Sturm sequences to count and verify whether each
  33. *> resulting interval has the correct number of singular values (using
  34. *> DSVDCT). Here EPS=TOL*MAX(N/10,1)*MAZHEP, where MACHEP is the
  35. *> machine precision. The routine assumes the singular values are sorted
  36. *> with SVD(1) the largest and SVD(N) smallest. If each interval
  37. *> contains the correct number of singular values, INFO = 0 is returned,
  38. *> otherwise INFO is the index of the first singular value in the first
  39. *> bad interval.
  40. *> \endverbatim
  41. *
  42. * Arguments:
  43. * ==========
  44. *
  45. *> \param[in] N
  46. *> \verbatim
  47. *> N is INTEGER
  48. *> The dimension of the bidiagonal matrix B.
  49. *> \endverbatim
  50. *>
  51. *> \param[in] S
  52. *> \verbatim
  53. *> S is DOUBLE PRECISION array, dimension (N)
  54. *> The diagonal entries of the bidiagonal matrix B.
  55. *> \endverbatim
  56. *>
  57. *> \param[in] E
  58. *> \verbatim
  59. *> E is DOUBLE PRECISION array, dimension (N-1)
  60. *> The superdiagonal entries of the bidiagonal matrix B.
  61. *> \endverbatim
  62. *>
  63. *> \param[in] SVD
  64. *> \verbatim
  65. *> SVD is DOUBLE PRECISION array, dimension (N)
  66. *> The computed singular values to be checked.
  67. *> \endverbatim
  68. *>
  69. *> \param[in] TOL
  70. *> \verbatim
  71. *> TOL is DOUBLE PRECISION
  72. *> Error tolerance for checking, a multiplier of the
  73. *> machine precision.
  74. *> \endverbatim
  75. *>
  76. *> \param[out] INFO
  77. *> \verbatim
  78. *> INFO is INTEGER
  79. *> =0 if the singular values are all correct (to within
  80. *> 1 +- TOL*MAZHEPS)
  81. *> >0 if the interval containing the INFO-th singular value
  82. *> contains the incorrect number of singular values.
  83. *> \endverbatim
  84. *
  85. * Authors:
  86. * ========
  87. *
  88. *> \author Univ. of Tennessee
  89. *> \author Univ. of California Berkeley
  90. *> \author Univ. of Colorado Denver
  91. *> \author NAG Ltd.
  92. *
  93. *> \ingroup double_eig
  94. *
  95. * =====================================================================
  96. SUBROUTINE DSVDCH( N, S, E, SVD, TOL, INFO )
  97. *
  98. * -- LAPACK test routine --
  99. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  100. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  101. *
  102. * .. Scalar Arguments ..
  103. INTEGER INFO, N
  104. DOUBLE PRECISION TOL
  105. * ..
  106. * .. Array Arguments ..
  107. DOUBLE PRECISION E( * ), S( * ), SVD( * )
  108. * ..
  109. *
  110. * =====================================================================
  111. *
  112. * .. Parameters ..
  113. DOUBLE PRECISION ONE
  114. PARAMETER ( ONE = 1.0D0 )
  115. DOUBLE PRECISION ZERO
  116. PARAMETER ( ZERO = 0.0D0 )
  117. * ..
  118. * .. Local Scalars ..
  119. INTEGER BPNT, COUNT, NUML, NUMU, TPNT
  120. DOUBLE PRECISION EPS, LOWER, OVFL, TUPPR, UNFL, UNFLEP, UPPER
  121. * ..
  122. * .. External Functions ..
  123. DOUBLE PRECISION DLAMCH
  124. EXTERNAL DLAMCH
  125. * ..
  126. * .. External Subroutines ..
  127. EXTERNAL DSVDCT
  128. * ..
  129. * .. Intrinsic Functions ..
  130. INTRINSIC MAX, SQRT
  131. * ..
  132. * .. Executable Statements ..
  133. *
  134. * Get machine constants
  135. *
  136. INFO = 0
  137. IF( N.LE.0 )
  138. $ RETURN
  139. UNFL = DLAMCH( 'Safe minimum' )
  140. OVFL = DLAMCH( 'Overflow' )
  141. EPS = DLAMCH( 'Epsilon' )*DLAMCH( 'Base' )
  142. *
  143. * UNFLEP is chosen so that when an eigenvalue is multiplied by the
  144. * scale factor sqrt(OVFL)*sqrt(sqrt(UNFL))/MX in DSVDCT, it exceeds
  145. * sqrt(UNFL), which is the lower limit for DSVDCT.
  146. *
  147. UNFLEP = ( SQRT( SQRT( UNFL ) ) / SQRT( OVFL ) )*SVD( 1 ) +
  148. $ UNFL / EPS
  149. *
  150. * The value of EPS works best when TOL .GE. 10.
  151. *
  152. EPS = TOL*MAX( N / 10, 1 )*EPS
  153. *
  154. * TPNT points to singular value at right endpoint of interval
  155. * BPNT points to singular value at left endpoint of interval
  156. *
  157. TPNT = 1
  158. BPNT = 1
  159. *
  160. * Begin loop over all intervals
  161. *
  162. 10 CONTINUE
  163. UPPER = ( ONE+EPS )*SVD( TPNT ) + UNFLEP
  164. LOWER = ( ONE-EPS )*SVD( BPNT ) - UNFLEP
  165. IF( LOWER.LE.UNFLEP )
  166. $ LOWER = -UPPER
  167. *
  168. * Begin loop merging overlapping intervals
  169. *
  170. 20 CONTINUE
  171. IF( BPNT.EQ.N )
  172. $ GO TO 30
  173. TUPPR = ( ONE+EPS )*SVD( BPNT+1 ) + UNFLEP
  174. IF( TUPPR.LT.LOWER )
  175. $ GO TO 30
  176. *
  177. * Merge
  178. *
  179. BPNT = BPNT + 1
  180. LOWER = ( ONE-EPS )*SVD( BPNT ) - UNFLEP
  181. IF( LOWER.LE.UNFLEP )
  182. $ LOWER = -UPPER
  183. GO TO 20
  184. 30 CONTINUE
  185. *
  186. * Count singular values in interval [ LOWER, UPPER ]
  187. *
  188. CALL DSVDCT( N, S, E, LOWER, NUML )
  189. CALL DSVDCT( N, S, E, UPPER, NUMU )
  190. COUNT = NUMU - NUML
  191. IF( LOWER.LT.ZERO )
  192. $ COUNT = COUNT / 2
  193. IF( COUNT.NE.BPNT-TPNT+1 ) THEN
  194. *
  195. * Wrong number of singular values in interval
  196. *
  197. INFO = TPNT
  198. GO TO 40
  199. END IF
  200. TPNT = BPNT + 1
  201. BPNT = TPNT
  202. IF( TPNT.LE.N )
  203. $ GO TO 10
  204. 40 CONTINUE
  205. RETURN
  206. *
  207. * End of DSVDCH
  208. *
  209. END