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.

dopmtr.f 8.7 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336
  1. *> \brief \b DOPMTR
  2. *
  3. * =========== DOCUMENTATION ===========
  4. *
  5. * Online html documentation available at
  6. * http://www.netlib.org/lapack/explore-html/
  7. *
  8. *> \htmlonly
  9. *> Download DOPMTR + dependencies
  10. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dopmtr.f">
  11. *> [TGZ]</a>
  12. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dopmtr.f">
  13. *> [ZIP]</a>
  14. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dopmtr.f">
  15. *> [TXT]</a>
  16. *> \endhtmlonly
  17. *
  18. * Definition:
  19. * ===========
  20. *
  21. * SUBROUTINE DOPMTR( SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC, WORK,
  22. * INFO )
  23. *
  24. * .. Scalar Arguments ..
  25. * CHARACTER SIDE, TRANS, UPLO
  26. * INTEGER INFO, LDC, M, N
  27. * ..
  28. * .. Array Arguments ..
  29. * DOUBLE PRECISION AP( * ), C( LDC, * ), TAU( * ), WORK( * )
  30. * ..
  31. *
  32. *
  33. *> \par Purpose:
  34. * =============
  35. *>
  36. *> \verbatim
  37. *>
  38. *> DOPMTR overwrites the general real M-by-N matrix C with
  39. *>
  40. *> SIDE = 'L' SIDE = 'R'
  41. *> TRANS = 'N': Q * C C * Q
  42. *> TRANS = 'T': Q**T * C C * Q**T
  43. *>
  44. *> where Q is a real orthogonal matrix of order nq, with nq = m if
  45. *> SIDE = 'L' and nq = n if SIDE = 'R'. Q is defined as the product of
  46. *> nq-1 elementary reflectors, as returned by DSPTRD using packed
  47. *> storage:
  48. *>
  49. *> if UPLO = 'U', Q = H(nq-1) . . . H(2) H(1);
  50. *>
  51. *> if UPLO = 'L', Q = H(1) H(2) . . . H(nq-1).
  52. *> \endverbatim
  53. *
  54. * Arguments:
  55. * ==========
  56. *
  57. *> \param[in] SIDE
  58. *> \verbatim
  59. *> SIDE is CHARACTER*1
  60. *> = 'L': apply Q or Q**T from the Left;
  61. *> = 'R': apply Q or Q**T from the Right.
  62. *> \endverbatim
  63. *>
  64. *> \param[in] UPLO
  65. *> \verbatim
  66. *> UPLO is CHARACTER*1
  67. *> = 'U': Upper triangular packed storage used in previous
  68. *> call to DSPTRD;
  69. *> = 'L': Lower triangular packed storage used in previous
  70. *> call to DSPTRD.
  71. *> \endverbatim
  72. *>
  73. *> \param[in] TRANS
  74. *> \verbatim
  75. *> TRANS is CHARACTER*1
  76. *> = 'N': No transpose, apply Q;
  77. *> = 'T': Transpose, apply Q**T.
  78. *> \endverbatim
  79. *>
  80. *> \param[in] M
  81. *> \verbatim
  82. *> M is INTEGER
  83. *> The number of rows of the matrix C. M >= 0.
  84. *> \endverbatim
  85. *>
  86. *> \param[in] N
  87. *> \verbatim
  88. *> N is INTEGER
  89. *> The number of columns of the matrix C. N >= 0.
  90. *> \endverbatim
  91. *>
  92. *> \param[in] AP
  93. *> \verbatim
  94. *> AP is DOUBLE PRECISION array, dimension
  95. *> (M*(M+1)/2) if SIDE = 'L'
  96. *> (N*(N+1)/2) if SIDE = 'R'
  97. *> The vectors which define the elementary reflectors, as
  98. *> returned by DSPTRD. AP is modified by the routine but
  99. *> restored on exit.
  100. *> \endverbatim
  101. *>
  102. *> \param[in] TAU
  103. *> \verbatim
  104. *> TAU is DOUBLE PRECISION array, dimension (M-1) if SIDE = 'L'
  105. *> or (N-1) if SIDE = 'R'
  106. *> TAU(i) must contain the scalar factor of the elementary
  107. *> reflector H(i), as returned by DSPTRD.
  108. *> \endverbatim
  109. *>
  110. *> \param[in,out] C
  111. *> \verbatim
  112. *> C is DOUBLE PRECISION array, dimension (LDC,N)
  113. *> On entry, the M-by-N matrix C.
  114. *> On exit, C is overwritten by Q*C or Q**T*C or C*Q**T or C*Q.
  115. *> \endverbatim
  116. *>
  117. *> \param[in] LDC
  118. *> \verbatim
  119. *> LDC is INTEGER
  120. *> The leading dimension of the array C. LDC >= max(1,M).
  121. *> \endverbatim
  122. *>
  123. *> \param[out] WORK
  124. *> \verbatim
  125. *> WORK is DOUBLE PRECISION array, dimension
  126. *> (N) if SIDE = 'L'
  127. *> (M) if SIDE = 'R'
  128. *> \endverbatim
  129. *>
  130. *> \param[out] INFO
  131. *> \verbatim
  132. *> INFO is INTEGER
  133. *> = 0: successful exit
  134. *> < 0: if INFO = -i, the i-th argument had an illegal value
  135. *> \endverbatim
  136. *
  137. * Authors:
  138. * ========
  139. *
  140. *> \author Univ. of Tennessee
  141. *> \author Univ. of California Berkeley
  142. *> \author Univ. of Colorado Denver
  143. *> \author NAG Ltd.
  144. *
  145. *> \ingroup doubleOTHERcomputational
  146. *
  147. * =====================================================================
  148. SUBROUTINE DOPMTR( SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC, WORK,
  149. $ INFO )
  150. *
  151. * -- LAPACK computational routine --
  152. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  153. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  154. *
  155. * .. Scalar Arguments ..
  156. CHARACTER SIDE, TRANS, UPLO
  157. INTEGER INFO, LDC, M, N
  158. * ..
  159. * .. Array Arguments ..
  160. DOUBLE PRECISION AP( * ), C( LDC, * ), TAU( * ), WORK( * )
  161. * ..
  162. *
  163. * =====================================================================
  164. *
  165. * .. Parameters ..
  166. DOUBLE PRECISION ONE
  167. PARAMETER ( ONE = 1.0D+0 )
  168. * ..
  169. * .. Local Scalars ..
  170. LOGICAL FORWRD, LEFT, NOTRAN, UPPER
  171. INTEGER I, I1, I2, I3, IC, II, JC, MI, NI, NQ
  172. DOUBLE PRECISION AII
  173. * ..
  174. * .. External Functions ..
  175. LOGICAL LSAME
  176. EXTERNAL LSAME
  177. * ..
  178. * .. External Subroutines ..
  179. EXTERNAL DLARF, XERBLA
  180. * ..
  181. * .. Intrinsic Functions ..
  182. INTRINSIC MAX
  183. * ..
  184. * .. Executable Statements ..
  185. *
  186. * Test the input arguments
  187. *
  188. INFO = 0
  189. LEFT = LSAME( SIDE, 'L' )
  190. NOTRAN = LSAME( TRANS, 'N' )
  191. UPPER = LSAME( UPLO, 'U' )
  192. *
  193. * NQ is the order of Q
  194. *
  195. IF( LEFT ) THEN
  196. NQ = M
  197. ELSE
  198. NQ = N
  199. END IF
  200. IF( .NOT.LEFT .AND. .NOT.LSAME( SIDE, 'R' ) ) THEN
  201. INFO = -1
  202. ELSE IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
  203. INFO = -2
  204. ELSE IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'T' ) ) THEN
  205. INFO = -3
  206. ELSE IF( M.LT.0 ) THEN
  207. INFO = -4
  208. ELSE IF( N.LT.0 ) THEN
  209. INFO = -5
  210. ELSE IF( LDC.LT.MAX( 1, M ) ) THEN
  211. INFO = -9
  212. END IF
  213. IF( INFO.NE.0 ) THEN
  214. CALL XERBLA( 'DOPMTR', -INFO )
  215. RETURN
  216. END IF
  217. *
  218. * Quick return if possible
  219. *
  220. IF( M.EQ.0 .OR. N.EQ.0 )
  221. $ RETURN
  222. *
  223. IF( UPPER ) THEN
  224. *
  225. * Q was determined by a call to DSPTRD with UPLO = 'U'
  226. *
  227. FORWRD = ( LEFT .AND. NOTRAN ) .OR.
  228. $ ( .NOT.LEFT .AND. .NOT.NOTRAN )
  229. *
  230. IF( FORWRD ) THEN
  231. I1 = 1
  232. I2 = NQ - 1
  233. I3 = 1
  234. II = 2
  235. ELSE
  236. I1 = NQ - 1
  237. I2 = 1
  238. I3 = -1
  239. II = NQ*( NQ+1 ) / 2 - 1
  240. END IF
  241. *
  242. IF( LEFT ) THEN
  243. NI = N
  244. ELSE
  245. MI = M
  246. END IF
  247. *
  248. DO 10 I = I1, I2, I3
  249. IF( LEFT ) THEN
  250. *
  251. * H(i) is applied to C(1:i,1:n)
  252. *
  253. MI = I
  254. ELSE
  255. *
  256. * H(i) is applied to C(1:m,1:i)
  257. *
  258. NI = I
  259. END IF
  260. *
  261. * Apply H(i)
  262. *
  263. AII = AP( II )
  264. AP( II ) = ONE
  265. CALL DLARF( SIDE, MI, NI, AP( II-I+1 ), 1, TAU( I ), C, LDC,
  266. $ WORK )
  267. AP( II ) = AII
  268. *
  269. IF( FORWRD ) THEN
  270. II = II + I + 2
  271. ELSE
  272. II = II - I - 1
  273. END IF
  274. 10 CONTINUE
  275. ELSE
  276. *
  277. * Q was determined by a call to DSPTRD with UPLO = 'L'.
  278. *
  279. FORWRD = ( LEFT .AND. .NOT.NOTRAN ) .OR.
  280. $ ( .NOT.LEFT .AND. NOTRAN )
  281. *
  282. IF( FORWRD ) THEN
  283. I1 = 1
  284. I2 = NQ - 1
  285. I3 = 1
  286. II = 2
  287. ELSE
  288. I1 = NQ - 1
  289. I2 = 1
  290. I3 = -1
  291. II = NQ*( NQ+1 ) / 2 - 1
  292. END IF
  293. *
  294. IF( LEFT ) THEN
  295. NI = N
  296. JC = 1
  297. ELSE
  298. MI = M
  299. IC = 1
  300. END IF
  301. *
  302. DO 20 I = I1, I2, I3
  303. AII = AP( II )
  304. AP( II ) = ONE
  305. IF( LEFT ) THEN
  306. *
  307. * H(i) is applied to C(i+1:m,1:n)
  308. *
  309. MI = M - I
  310. IC = I + 1
  311. ELSE
  312. *
  313. * H(i) is applied to C(1:m,i+1:n)
  314. *
  315. NI = N - I
  316. JC = I + 1
  317. END IF
  318. *
  319. * Apply H(i)
  320. *
  321. CALL DLARF( SIDE, MI, NI, AP( II ), 1, TAU( I ),
  322. $ C( IC, JC ), LDC, WORK )
  323. AP( II ) = AII
  324. *
  325. IF( FORWRD ) THEN
  326. II = II + NQ - I + 1
  327. ELSE
  328. II = II - NQ + I - 2
  329. END IF
  330. 20 CONTINUE
  331. END IF
  332. RETURN
  333. *
  334. * End of DOPMTR
  335. *
  336. END