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.

slasd8.f 9.7 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321
  1. *> \brief \b SLASD8 finds the square roots of the roots of the secular equation, and stores, for each element in D, the distance to its two nearest poles. Used by sbdsdc.
  2. *
  3. * =========== DOCUMENTATION ===========
  4. *
  5. * Online html documentation available at
  6. * http://www.netlib.org/lapack/explore-html/
  7. *
  8. *> \htmlonly
  9. *> Download SLASD8 + dependencies
  10. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slasd8.f">
  11. *> [TGZ]</a>
  12. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slasd8.f">
  13. *> [ZIP]</a>
  14. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slasd8.f">
  15. *> [TXT]</a>
  16. *> \endhtmlonly
  17. *
  18. * Definition:
  19. * ===========
  20. *
  21. * SUBROUTINE SLASD8( ICOMPQ, K, D, Z, VF, VL, DIFL, DIFR, LDDIFR,
  22. * DSIGMA, WORK, INFO )
  23. *
  24. * .. Scalar Arguments ..
  25. * INTEGER ICOMPQ, INFO, K, LDDIFR
  26. * ..
  27. * .. Array Arguments ..
  28. * REAL D( * ), DIFL( * ), DIFR( LDDIFR, * ),
  29. * $ DSIGMA( * ), VF( * ), VL( * ), WORK( * ),
  30. * $ Z( * )
  31. * ..
  32. *
  33. *
  34. *> \par Purpose:
  35. * =============
  36. *>
  37. *> \verbatim
  38. *>
  39. *> SLASD8 finds the square roots of the roots of the secular equation,
  40. *> as defined by the values in DSIGMA and Z. It makes the appropriate
  41. *> calls to SLASD4, and stores, for each element in D, the distance
  42. *> to its two nearest poles (elements in DSIGMA). It also updates
  43. *> the arrays VF and VL, the first and last components of all the
  44. *> right singular vectors of the original bidiagonal matrix.
  45. *>
  46. *> SLASD8 is called from SLASD6.
  47. *> \endverbatim
  48. *
  49. * Arguments:
  50. * ==========
  51. *
  52. *> \param[in] ICOMPQ
  53. *> \verbatim
  54. *> ICOMPQ is INTEGER
  55. *> Specifies whether singular vectors are to be computed in
  56. *> factored form in the calling routine:
  57. *> = 0: Compute singular values only.
  58. *> = 1: Compute singular vectors in factored form as well.
  59. *> \endverbatim
  60. *>
  61. *> \param[in] K
  62. *> \verbatim
  63. *> K is INTEGER
  64. *> The number of terms in the rational function to be solved
  65. *> by SLASD4. K >= 1.
  66. *> \endverbatim
  67. *>
  68. *> \param[out] D
  69. *> \verbatim
  70. *> D is REAL array, dimension ( K )
  71. *> On output, D contains the updated singular values.
  72. *> \endverbatim
  73. *>
  74. *> \param[in,out] Z
  75. *> \verbatim
  76. *> Z is REAL array, dimension ( K )
  77. *> On entry, the first K elements of this array contain the
  78. *> components of the deflation-adjusted updating row vector.
  79. *> On exit, Z is updated.
  80. *> \endverbatim
  81. *>
  82. *> \param[in,out] VF
  83. *> \verbatim
  84. *> VF is REAL array, dimension ( K )
  85. *> On entry, VF contains information passed through DBEDE8.
  86. *> On exit, VF contains the first K components of the first
  87. *> components of all right singular vectors of the bidiagonal
  88. *> matrix.
  89. *> \endverbatim
  90. *>
  91. *> \param[in,out] VL
  92. *> \verbatim
  93. *> VL is REAL array, dimension ( K )
  94. *> On entry, VL contains information passed through DBEDE8.
  95. *> On exit, VL contains the first K components of the last
  96. *> components of all right singular vectors of the bidiagonal
  97. *> matrix.
  98. *> \endverbatim
  99. *>
  100. *> \param[out] DIFL
  101. *> \verbatim
  102. *> DIFL is REAL array, dimension ( K )
  103. *> On exit, DIFL(I) = D(I) - DSIGMA(I).
  104. *> \endverbatim
  105. *>
  106. *> \param[out] DIFR
  107. *> \verbatim
  108. *> DIFR is REAL array,
  109. *> dimension ( LDDIFR, 2 ) if ICOMPQ = 1 and
  110. *> dimension ( K ) if ICOMPQ = 0.
  111. *> On exit, DIFR(I,1) = D(I) - DSIGMA(I+1), DIFR(K,1) is not
  112. *> defined and will not be referenced.
  113. *>
  114. *> If ICOMPQ = 1, DIFR(1:K,2) is an array containing the
  115. *> normalizing factors for the right singular vector matrix.
  116. *> \endverbatim
  117. *>
  118. *> \param[in] LDDIFR
  119. *> \verbatim
  120. *> LDDIFR is INTEGER
  121. *> The leading dimension of DIFR, must be at least K.
  122. *> \endverbatim
  123. *>
  124. *> \param[in] DSIGMA
  125. *> \verbatim
  126. *> DSIGMA is REAL array, dimension ( K )
  127. *> On entry, the first K elements of this array contain the old
  128. *> roots of the deflated updating problem. These are the poles
  129. *> of the secular equation.
  130. *> \endverbatim
  131. *>
  132. *> \param[out] WORK
  133. *> \verbatim
  134. *> WORK is REAL array, dimension (3*K)
  135. *> \endverbatim
  136. *>
  137. *> \param[out] INFO
  138. *> \verbatim
  139. *> INFO is INTEGER
  140. *> = 0: successful exit.
  141. *> < 0: if INFO = -i, the i-th argument had an illegal value.
  142. *> > 0: if INFO = 1, a singular value did not converge
  143. *> \endverbatim
  144. *
  145. * Authors:
  146. * ========
  147. *
  148. *> \author Univ. of Tennessee
  149. *> \author Univ. of California Berkeley
  150. *> \author Univ. of Colorado Denver
  151. *> \author NAG Ltd.
  152. *
  153. *> \ingroup OTHERauxiliary
  154. *
  155. *> \par Contributors:
  156. * ==================
  157. *>
  158. *> Ming Gu and Huan Ren, Computer Science Division, University of
  159. *> California at Berkeley, USA
  160. *>
  161. * =====================================================================
  162. SUBROUTINE SLASD8( ICOMPQ, K, D, Z, VF, VL, DIFL, DIFR, LDDIFR,
  163. $ DSIGMA, WORK, INFO )
  164. *
  165. * -- LAPACK auxiliary routine --
  166. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  167. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  168. *
  169. * .. Scalar Arguments ..
  170. INTEGER ICOMPQ, INFO, K, LDDIFR
  171. * ..
  172. * .. Array Arguments ..
  173. REAL D( * ), DIFL( * ), DIFR( LDDIFR, * ),
  174. $ DSIGMA( * ), VF( * ), VL( * ), WORK( * ),
  175. $ Z( * )
  176. * ..
  177. *
  178. * =====================================================================
  179. *
  180. * .. Parameters ..
  181. REAL ONE
  182. PARAMETER ( ONE = 1.0E+0 )
  183. * ..
  184. * .. Local Scalars ..
  185. INTEGER I, IWK1, IWK2, IWK2I, IWK3, IWK3I, J
  186. REAL DIFLJ, DIFRJ, DJ, DSIGJ, DSIGJP, RHO, TEMP
  187. * ..
  188. * .. External Subroutines ..
  189. EXTERNAL SCOPY, SLASCL, SLASD4, SLASET, XERBLA
  190. * ..
  191. * .. External Functions ..
  192. REAL SDOT, SLAMC3, SNRM2
  193. EXTERNAL SDOT, SLAMC3, SNRM2
  194. * ..
  195. * .. Intrinsic Functions ..
  196. INTRINSIC ABS, SIGN, SQRT
  197. * ..
  198. * .. Executable Statements ..
  199. *
  200. * Test the input parameters.
  201. *
  202. INFO = 0
  203. *
  204. IF( ( ICOMPQ.LT.0 ) .OR. ( ICOMPQ.GT.1 ) ) THEN
  205. INFO = -1
  206. ELSE IF( K.LT.1 ) THEN
  207. INFO = -2
  208. ELSE IF( LDDIFR.LT.K ) THEN
  209. INFO = -9
  210. END IF
  211. IF( INFO.NE.0 ) THEN
  212. CALL XERBLA( 'SLASD8', -INFO )
  213. RETURN
  214. END IF
  215. *
  216. * Quick return if possible
  217. *
  218. IF( K.EQ.1 ) THEN
  219. D( 1 ) = ABS( Z( 1 ) )
  220. DIFL( 1 ) = D( 1 )
  221. IF( ICOMPQ.EQ.1 ) THEN
  222. DIFL( 2 ) = ONE
  223. DIFR( 1, 2 ) = ONE
  224. END IF
  225. RETURN
  226. END IF
  227. *
  228. * Book keeping.
  229. *
  230. IWK1 = 1
  231. IWK2 = IWK1 + K
  232. IWK3 = IWK2 + K
  233. IWK2I = IWK2 - 1
  234. IWK3I = IWK3 - 1
  235. *
  236. * Normalize Z.
  237. *
  238. RHO = SNRM2( K, Z, 1 )
  239. CALL SLASCL( 'G', 0, 0, RHO, ONE, K, 1, Z, K, INFO )
  240. RHO = RHO*RHO
  241. *
  242. * Initialize WORK(IWK3).
  243. *
  244. CALL SLASET( 'A', K, 1, ONE, ONE, WORK( IWK3 ), K )
  245. *
  246. * Compute the updated singular values, the arrays DIFL, DIFR,
  247. * and the updated Z.
  248. *
  249. DO 40 J = 1, K
  250. CALL SLASD4( K, J, DSIGMA, Z, WORK( IWK1 ), RHO, D( J ),
  251. $ WORK( IWK2 ), INFO )
  252. *
  253. * If the root finder fails, report the convergence failure.
  254. *
  255. IF( INFO.NE.0 ) THEN
  256. RETURN
  257. END IF
  258. WORK( IWK3I+J ) = WORK( IWK3I+J )*WORK( J )*WORK( IWK2I+J )
  259. DIFL( J ) = -WORK( J )
  260. DIFR( J, 1 ) = -WORK( J+1 )
  261. DO 20 I = 1, J - 1
  262. WORK( IWK3I+I ) = WORK( IWK3I+I )*WORK( I )*
  263. $ WORK( IWK2I+I ) / ( DSIGMA( I )-
  264. $ DSIGMA( J ) ) / ( DSIGMA( I )+
  265. $ DSIGMA( J ) )
  266. 20 CONTINUE
  267. DO 30 I = J + 1, K
  268. WORK( IWK3I+I ) = WORK( IWK3I+I )*WORK( I )*
  269. $ WORK( IWK2I+I ) / ( DSIGMA( I )-
  270. $ DSIGMA( J ) ) / ( DSIGMA( I )+
  271. $ DSIGMA( J ) )
  272. 30 CONTINUE
  273. 40 CONTINUE
  274. *
  275. * Compute updated Z.
  276. *
  277. DO 50 I = 1, K
  278. Z( I ) = SIGN( SQRT( ABS( WORK( IWK3I+I ) ) ), Z( I ) )
  279. 50 CONTINUE
  280. *
  281. * Update VF and VL.
  282. *
  283. DO 80 J = 1, K
  284. DIFLJ = DIFL( J )
  285. DJ = D( J )
  286. DSIGJ = -DSIGMA( J )
  287. IF( J.LT.K ) THEN
  288. DIFRJ = -DIFR( J, 1 )
  289. DSIGJP = -DSIGMA( J+1 )
  290. END IF
  291. WORK( J ) = -Z( J ) / DIFLJ / ( DSIGMA( J )+DJ )
  292. *
  293. * Use calls to the subroutine SLAMC3 to enforce the parentheses
  294. * (x+y)+z. The goal is to prevent optimizing compilers
  295. * from doing x+(y+z).
  296. *
  297. DO 60 I = 1, J - 1
  298. WORK( I ) = Z( I ) / ( SLAMC3( DSIGMA( I ), DSIGJ )-DIFLJ )
  299. $ / ( DSIGMA( I )+DJ )
  300. 60 CONTINUE
  301. DO 70 I = J + 1, K
  302. WORK( I ) = Z( I ) / ( SLAMC3( DSIGMA( I ), DSIGJP )+DIFRJ )
  303. $ / ( DSIGMA( I )+DJ )
  304. 70 CONTINUE
  305. TEMP = SNRM2( K, WORK, 1 )
  306. WORK( IWK2I+J ) = SDOT( K, WORK, 1, VF, 1 ) / TEMP
  307. WORK( IWK3I+J ) = SDOT( K, WORK, 1, VL, 1 ) / TEMP
  308. IF( ICOMPQ.EQ.1 ) THEN
  309. DIFR( J, 2 ) = TEMP
  310. END IF
  311. 80 CONTINUE
  312. *
  313. CALL SCOPY( K, WORK( IWK2 ), 1, VF, 1 )
  314. CALL SCOPY( K, WORK( IWK3 ), 1, VL, 1 )
  315. *
  316. RETURN
  317. *
  318. * End of SLASD8
  319. *
  320. END