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.

dorbdb1.f 9.9 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323
  1. *> \brief \b DORBDB1
  2. *
  3. * =========== DOCUMENTATION ===========
  4. *
  5. * Online html documentation available at
  6. * http://www.netlib.org/lapack/explore-html/
  7. *
  8. *> \htmlonly
  9. *> Download DORBDB1 + dependencies
  10. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dorbdb1.f">
  11. *> [TGZ]</a>
  12. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dorbdb1.f">
  13. *> [ZIP]</a>
  14. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dorbdb1.f">
  15. *> [TXT]</a>
  16. *> \endhtmlonly
  17. *
  18. * Definition:
  19. * ===========
  20. *
  21. * SUBROUTINE DORBDB1( M, P, Q, X11, LDX11, X21, LDX21, THETA, PHI,
  22. * TAUP1, TAUP2, TAUQ1, WORK, LWORK, INFO )
  23. *
  24. * .. Scalar Arguments ..
  25. * INTEGER INFO, LWORK, M, P, Q, LDX11, LDX21
  26. * ..
  27. * .. Array Arguments ..
  28. * DOUBLE PRECISION PHI(*), THETA(*)
  29. * DOUBLE PRECISION TAUP1(*), TAUP2(*), TAUQ1(*), WORK(*),
  30. * $ X11(LDX11,*), X21(LDX21,*)
  31. * ..
  32. *
  33. *
  34. *> \par Purpose:
  35. * =============
  36. *>
  37. *>\verbatim
  38. *>
  39. *> DORBDB1 simultaneously bidiagonalizes the blocks of a tall and skinny
  40. *> matrix X with orthonomal columns:
  41. *>
  42. *> [ B11 ]
  43. *> [ X11 ] [ P1 | ] [ 0 ]
  44. *> [-----] = [---------] [-----] Q1**T .
  45. *> [ X21 ] [ | P2 ] [ B21 ]
  46. *> [ 0 ]
  47. *>
  48. *> X11 is P-by-Q, and X21 is (M-P)-by-Q. Q must be no larger than P,
  49. *> M-P, or M-Q. Routines DORBDB2, DORBDB3, and DORBDB4 handle cases in
  50. *> which Q is not the minimum dimension.
  51. *>
  52. *> The orthogonal matrices P1, P2, and Q1 are P-by-P, (M-P)-by-(M-P),
  53. *> and (M-Q)-by-(M-Q), respectively. They are represented implicitly by
  54. *> Householder vectors.
  55. *>
  56. *> B11 and B12 are Q-by-Q bidiagonal matrices represented implicitly by
  57. *> angles THETA, PHI.
  58. *>
  59. *>\endverbatim
  60. *
  61. * Arguments:
  62. * ==========
  63. *
  64. *> \param[in] M
  65. *> \verbatim
  66. *> M is INTEGER
  67. *> The number of rows X11 plus the number of rows in X21.
  68. *> \endverbatim
  69. *>
  70. *> \param[in] P
  71. *> \verbatim
  72. *> P is INTEGER
  73. *> The number of rows in X11. 0 <= P <= M.
  74. *> \endverbatim
  75. *>
  76. *> \param[in] Q
  77. *> \verbatim
  78. *> Q is INTEGER
  79. *> The number of columns in X11 and X21. 0 <= Q <=
  80. *> MIN(P,M-P,M-Q).
  81. *> \endverbatim
  82. *>
  83. *> \param[in,out] X11
  84. *> \verbatim
  85. *> X11 is DOUBLE PRECISION array, dimension (LDX11,Q)
  86. *> On entry, the top block of the matrix X to be reduced. On
  87. *> exit, the columns of tril(X11) specify reflectors for P1 and
  88. *> the rows of triu(X11,1) specify reflectors for Q1.
  89. *> \endverbatim
  90. *>
  91. *> \param[in] LDX11
  92. *> \verbatim
  93. *> LDX11 is INTEGER
  94. *> The leading dimension of X11. LDX11 >= P.
  95. *> \endverbatim
  96. *>
  97. *> \param[in,out] X21
  98. *> \verbatim
  99. *> X21 is DOUBLE PRECISION array, dimension (LDX21,Q)
  100. *> On entry, the bottom block of the matrix X to be reduced. On
  101. *> exit, the columns of tril(X21) specify reflectors for P2.
  102. *> \endverbatim
  103. *>
  104. *> \param[in] LDX21
  105. *> \verbatim
  106. *> LDX21 is INTEGER
  107. *> The leading dimension of X21. LDX21 >= M-P.
  108. *> \endverbatim
  109. *>
  110. *> \param[out] THETA
  111. *> \verbatim
  112. *> THETA is DOUBLE PRECISION array, dimension (Q)
  113. *> The entries of the bidiagonal blocks B11, B21 are defined by
  114. *> THETA and PHI. See Further Details.
  115. *> \endverbatim
  116. *>
  117. *> \param[out] PHI
  118. *> \verbatim
  119. *> PHI is DOUBLE PRECISION array, dimension (Q-1)
  120. *> The entries of the bidiagonal blocks B11, B21 are defined by
  121. *> THETA and PHI. See Further Details.
  122. *> \endverbatim
  123. *>
  124. *> \param[out] TAUP1
  125. *> \verbatim
  126. *> TAUP1 is DOUBLE PRECISION array, dimension (P)
  127. *> The scalar factors of the elementary reflectors that define
  128. *> P1.
  129. *> \endverbatim
  130. *>
  131. *> \param[out] TAUP2
  132. *> \verbatim
  133. *> TAUP2 is DOUBLE PRECISION array, dimension (M-P)
  134. *> The scalar factors of the elementary reflectors that define
  135. *> P2.
  136. *> \endverbatim
  137. *>
  138. *> \param[out] TAUQ1
  139. *> \verbatim
  140. *> TAUQ1 is DOUBLE PRECISION array, dimension (Q)
  141. *> The scalar factors of the elementary reflectors that define
  142. *> Q1.
  143. *> \endverbatim
  144. *>
  145. *> \param[out] WORK
  146. *> \verbatim
  147. *> WORK is DOUBLE PRECISION array, dimension (LWORK)
  148. *> \endverbatim
  149. *>
  150. *> \param[in] LWORK
  151. *> \verbatim
  152. *> LWORK is INTEGER
  153. *> The dimension of the array WORK. LWORK >= M-Q.
  154. *>
  155. *> If LWORK = -1, then a workspace query is assumed; the routine
  156. *> only calculates the optimal size of the WORK array, returns
  157. *> this value as the first entry of the WORK array, and no error
  158. *> message related to LWORK is issued by XERBLA.
  159. *> \endverbatim
  160. *>
  161. *> \param[out] INFO
  162. *> \verbatim
  163. *> INFO is INTEGER
  164. *> = 0: successful exit.
  165. *> < 0: if INFO = -i, the i-th argument had an illegal value.
  166. *> \endverbatim
  167. *>
  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 July 2012
  178. *
  179. *> \ingroup doubleOTHERcomputational
  180. *
  181. *> \par Further Details:
  182. * =====================
  183. *>
  184. *> \verbatim
  185. *>
  186. *> The upper-bidiagonal blocks B11, B21 are represented implicitly by
  187. *> angles THETA(1), ..., THETA(Q) and PHI(1), ..., PHI(Q-1). Every entry
  188. *> in each bidiagonal band is a product of a sine or cosine of a THETA
  189. *> with a sine or cosine of a PHI. See [1] or DORCSD for details.
  190. *>
  191. *> P1, P2, and Q1 are represented as products of elementary reflectors.
  192. *> See DORCSD2BY1 for details on generating P1, P2, and Q1 using DORGQR
  193. *> and DORGLQ.
  194. *> \endverbatim
  195. *
  196. *> \par References:
  197. * ================
  198. *>
  199. *> [1] Brian D. Sutton. Computing the complete CS decomposition. Numer.
  200. *> Algorithms, 50(1):33-65, 2009.
  201. *>
  202. * =====================================================================
  203. SUBROUTINE DORBDB1( M, P, Q, X11, LDX11, X21, LDX21, THETA, PHI,
  204. $ TAUP1, TAUP2, TAUQ1, WORK, LWORK, INFO )
  205. *
  206. * -- LAPACK computational routine (version 3.7.1) --
  207. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  208. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  209. * July 2012
  210. *
  211. * .. Scalar Arguments ..
  212. INTEGER INFO, LWORK, M, P, Q, LDX11, LDX21
  213. * ..
  214. * .. Array Arguments ..
  215. DOUBLE PRECISION PHI(*), THETA(*)
  216. DOUBLE PRECISION TAUP1(*), TAUP2(*), TAUQ1(*), WORK(*),
  217. $ X11(LDX11,*), X21(LDX21,*)
  218. * ..
  219. *
  220. * ====================================================================
  221. *
  222. * .. Parameters ..
  223. DOUBLE PRECISION ONE
  224. PARAMETER ( ONE = 1.0D0 )
  225. * ..
  226. * .. Local Scalars ..
  227. DOUBLE PRECISION C, S
  228. INTEGER CHILDINFO, I, ILARF, IORBDB5, LLARF, LORBDB5,
  229. $ LWORKMIN, LWORKOPT
  230. LOGICAL LQUERY
  231. * ..
  232. * .. External Subroutines ..
  233. EXTERNAL DLARF, DLARFGP, DORBDB5, DROT, XERBLA
  234. * ..
  235. * .. External Functions ..
  236. DOUBLE PRECISION DNRM2
  237. EXTERNAL DNRM2
  238. * ..
  239. * .. Intrinsic Function ..
  240. INTRINSIC ATAN2, COS, MAX, SIN, SQRT
  241. * ..
  242. * .. Executable Statements ..
  243. *
  244. * Test input arguments
  245. *
  246. INFO = 0
  247. LQUERY = LWORK .EQ. -1
  248. *
  249. IF( M .LT. 0 ) THEN
  250. INFO = -1
  251. ELSE IF( P .LT. Q .OR. M-P .LT. Q ) THEN
  252. INFO = -2
  253. ELSE IF( Q .LT. 0 .OR. M-Q .LT. Q ) THEN
  254. INFO = -3
  255. ELSE IF( LDX11 .LT. MAX( 1, P ) ) THEN
  256. INFO = -5
  257. ELSE IF( LDX21 .LT. MAX( 1, M-P ) ) THEN
  258. INFO = -7
  259. END IF
  260. *
  261. * Compute workspace
  262. *
  263. IF( INFO .EQ. 0 ) THEN
  264. ILARF = 2
  265. LLARF = MAX( P-1, M-P-1, Q-1 )
  266. IORBDB5 = 2
  267. LORBDB5 = Q-2
  268. LWORKOPT = MAX( ILARF+LLARF-1, IORBDB5+LORBDB5-1 )
  269. LWORKMIN = LWORKOPT
  270. WORK(1) = LWORKOPT
  271. IF( LWORK .LT. LWORKMIN .AND. .NOT.LQUERY ) THEN
  272. INFO = -14
  273. END IF
  274. END IF
  275. IF( INFO .NE. 0 ) THEN
  276. CALL XERBLA( 'DORBDB1', -INFO )
  277. RETURN
  278. ELSE IF( LQUERY ) THEN
  279. RETURN
  280. END IF
  281. *
  282. * Reduce columns 1, ..., Q of X11 and X21
  283. *
  284. DO I = 1, Q
  285. *
  286. CALL DLARFGP( P-I+1, X11(I,I), X11(I+1,I), 1, TAUP1(I) )
  287. CALL DLARFGP( M-P-I+1, X21(I,I), X21(I+1,I), 1, TAUP2(I) )
  288. THETA(I) = ATAN2( X21(I,I), X11(I,I) )
  289. C = COS( THETA(I) )
  290. S = SIN( THETA(I) )
  291. X11(I,I) = ONE
  292. X21(I,I) = ONE
  293. CALL DLARF( 'L', P-I+1, Q-I, X11(I,I), 1, TAUP1(I), X11(I,I+1),
  294. $ LDX11, WORK(ILARF) )
  295. CALL DLARF( 'L', M-P-I+1, Q-I, X21(I,I), 1, TAUP2(I),
  296. $ X21(I,I+1), LDX21, WORK(ILARF) )
  297. *
  298. IF( I .LT. Q ) THEN
  299. CALL DROT( Q-I, X11(I,I+1), LDX11, X21(I,I+1), LDX21, C, S )
  300. CALL DLARFGP( Q-I, X21(I,I+1), X21(I,I+2), LDX21, TAUQ1(I) )
  301. S = X21(I,I+1)
  302. X21(I,I+1) = ONE
  303. CALL DLARF( 'R', P-I, Q-I, X21(I,I+1), LDX21, TAUQ1(I),
  304. $ X11(I+1,I+1), LDX11, WORK(ILARF) )
  305. CALL DLARF( 'R', M-P-I, Q-I, X21(I,I+1), LDX21, TAUQ1(I),
  306. $ X21(I+1,I+1), LDX21, WORK(ILARF) )
  307. C = SQRT( DNRM2( P-I, X11(I+1,I+1), 1 )**2
  308. $ + DNRM2( M-P-I, X21(I+1,I+1), 1 )**2 )
  309. PHI(I) = ATAN2( S, C )
  310. CALL DORBDB5( P-I, M-P-I, Q-I-1, X11(I+1,I+1), 1,
  311. $ X21(I+1,I+1), 1, X11(I+1,I+2), LDX11,
  312. $ X21(I+1,I+2), LDX21, WORK(IORBDB5), LORBDB5,
  313. $ CHILDINFO )
  314. END IF
  315. *
  316. END DO
  317. *
  318. RETURN
  319. *
  320. * End of DORBDB1
  321. *
  322. END