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.

cgelqt3.f 6.7 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246
  1. *> \brief \b CGELQT3
  2. *
  3. * Definition:
  4. * ===========
  5. *
  6. * RECURSIVE SUBROUTINE CGELQT3( M, N, A, LDA, T, LDT, INFO )
  7. *
  8. * .. Scalar Arguments ..
  9. * INTEGER INFO, LDA, M, N, LDT
  10. * ..
  11. * .. Array Arguments ..
  12. * COMPLEX A( LDA, * ), T( LDT, * )
  13. * ..
  14. *
  15. *
  16. *> \par Purpose:
  17. * =============
  18. *>
  19. *> \verbatim
  20. *>
  21. *> CGELQT3 recursively computes a LQ factorization of a complex M-by-N
  22. *> matrix A, using the compact WY representation of Q.
  23. *>
  24. *> Based on the algorithm of Elmroth and Gustavson,
  25. *> IBM J. Res. Develop. Vol 44 No. 4 July 2000.
  26. *> \endverbatim
  27. *
  28. * Arguments:
  29. * ==========
  30. *
  31. *> \param[in] M
  32. *> \verbatim
  33. *> M is INTEGER
  34. *> The number of rows of the matrix A. M =< N.
  35. *> \endverbatim
  36. *>
  37. *> \param[in] N
  38. *> \verbatim
  39. *> N is INTEGER
  40. *> The number of columns of the matrix A. N >= 0.
  41. *> \endverbatim
  42. *>
  43. *> \param[in,out] A
  44. *> \verbatim
  45. *> A is COMPLEX array, dimension (LDA,N)
  46. *> On entry, the real M-by-N matrix A. On exit, the elements on and
  47. *> below the diagonal contain the N-by-N lower triangular matrix L; the
  48. *> elements above the diagonal are the rows of V. See below for
  49. *> further details.
  50. *> \endverbatim
  51. *>
  52. *> \param[in] LDA
  53. *> \verbatim
  54. *> LDA is INTEGER
  55. *> The leading dimension of the array A. LDA >= max(1,M).
  56. *> \endverbatim
  57. *>
  58. *> \param[out] T
  59. *> \verbatim
  60. *> T is COMPLEX array, dimension (LDT,N)
  61. *> The N-by-N upper triangular factor of the block reflector.
  62. *> The elements on and above the diagonal contain the block
  63. *> reflector T; the elements below the diagonal are not used.
  64. *> See below for further details.
  65. *> \endverbatim
  66. *>
  67. *> \param[in] LDT
  68. *> \verbatim
  69. *> LDT is INTEGER
  70. *> The leading dimension of the array T. LDT >= max(1,N).
  71. *> \endverbatim
  72. *>
  73. *> \param[out] INFO
  74. *> \verbatim
  75. *> INFO is INTEGER
  76. *> = 0: successful exit
  77. *> < 0: if INFO = -i, the i-th argument had an illegal value
  78. *> \endverbatim
  79. *
  80. * Authors:
  81. * ========
  82. *
  83. *> \author Univ. of Tennessee
  84. *> \author Univ. of California Berkeley
  85. *> \author Univ. of Colorado Denver
  86. *> \author NAG Ltd.
  87. *
  88. *> \date November 2017
  89. *
  90. *> \ingroup doubleGEcomputational
  91. *
  92. *> \par Further Details:
  93. * =====================
  94. *>
  95. *> \verbatim
  96. *>
  97. *> The matrix V stores the elementary reflectors H(i) in the i-th row
  98. *> above the diagonal. For example, if M=5 and N=3, the matrix V is
  99. *>
  100. *> V = ( 1 v1 v1 v1 v1 )
  101. *> ( 1 v2 v2 v2 )
  102. *> ( 1 v3 v3 v3 )
  103. *>
  104. *>
  105. *> where the vi's represent the vectors which define H(i), which are returned
  106. *> in the matrix A. The 1's along the diagonal of V are not stored in A. The
  107. *> block reflector H is then given by
  108. *>
  109. *> H = I - V * T * V**T
  110. *>
  111. *> where V**T is the transpose of V.
  112. *>
  113. *> For details of the algorithm, see Elmroth and Gustavson (cited above).
  114. *> \endverbatim
  115. *>
  116. * =====================================================================
  117. RECURSIVE SUBROUTINE CGELQT3( M, N, A, LDA, T, LDT, INFO )
  118. *
  119. * -- LAPACK computational routine (version 3.8.0) --
  120. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  121. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  122. * November 2017
  123. *
  124. * .. Scalar Arguments ..
  125. INTEGER INFO, LDA, M, N, LDT
  126. * ..
  127. * .. Array Arguments ..
  128. COMPLEX A( LDA, * ), T( LDT, * )
  129. * ..
  130. *
  131. * =====================================================================
  132. *
  133. * .. Parameters ..
  134. COMPLEX ONE, ZERO
  135. PARAMETER ( ONE = (1.0E+00,0.0E+00) )
  136. PARAMETER ( ZERO = (0.0E+00,0.0E+00))
  137. * ..
  138. * .. Local Scalars ..
  139. INTEGER I, I1, J, J1, M1, M2, IINFO
  140. * ..
  141. * .. External Subroutines ..
  142. EXTERNAL CLARFG, CTRMM, CGEMM, XERBLA
  143. * ..
  144. * .. Executable Statements ..
  145. *
  146. INFO = 0
  147. IF( M .LT. 0 ) THEN
  148. INFO = -1
  149. ELSE IF( N .LT. M ) THEN
  150. INFO = -2
  151. ELSE IF( LDA .LT. MAX( 1, M ) ) THEN
  152. INFO = -4
  153. ELSE IF( LDT .LT. MAX( 1, M ) ) THEN
  154. INFO = -6
  155. END IF
  156. IF( INFO.NE.0 ) THEN
  157. CALL XERBLA( 'CGELQT3', -INFO )
  158. RETURN
  159. END IF
  160. *
  161. IF( M.EQ.1 ) THEN
  162. *
  163. * Compute Householder transform when N=1
  164. *
  165. CALL CLARFG( N, A, A( 1, MIN( 2, N ) ), LDA, T )
  166. T(1,1)=CONJG(T(1,1))
  167. *
  168. ELSE
  169. *
  170. * Otherwise, split A into blocks...
  171. *
  172. M1 = M/2
  173. M2 = M-M1
  174. I1 = MIN( M1+1, M )
  175. J1 = MIN( M+1, N )
  176. *
  177. * Compute A(1:M1,1:N) <- (Y1,R1,T1), where Q1 = I - Y1 T1 Y1^H
  178. *
  179. CALL CGELQT3( M1, N, A, LDA, T, LDT, IINFO )
  180. *
  181. * Compute A(J1:M,1:N) = A(J1:M,1:N) Q1^H [workspace: T(1:N1,J1:N)]
  182. *
  183. DO I=1,M2
  184. DO J=1,M1
  185. T( I+M1, J ) = A( I+M1, J )
  186. END DO
  187. END DO
  188. CALL CTRMM( 'R', 'U', 'C', 'U', M2, M1, ONE,
  189. & A, LDA, T( I1, 1 ), LDT )
  190. *
  191. CALL CGEMM( 'N', 'C', M2, M1, N-M1, ONE, A( I1, I1 ), LDA,
  192. & A( 1, I1 ), LDA, ONE, T( I1, 1 ), LDT)
  193. *
  194. CALL CTRMM( 'R', 'U', 'N', 'N', M2, M1, ONE,
  195. & T, LDT, T( I1, 1 ), LDT )
  196. *
  197. CALL CGEMM( 'N', 'N', M2, N-M1, M1, -ONE, T( I1, 1 ), LDT,
  198. & A( 1, I1 ), LDA, ONE, A( I1, I1 ), LDA )
  199. *
  200. CALL CTRMM( 'R', 'U', 'N', 'U', M2, M1 , ONE,
  201. & A, LDA, T( I1, 1 ), LDT )
  202. *
  203. DO I=1,M2
  204. DO J=1,M1
  205. A( I+M1, J ) = A( I+M1, J ) - T( I+M1, J )
  206. T( I+M1, J )= ZERO
  207. END DO
  208. END DO
  209. *
  210. * Compute A(J1:M,J1:N) <- (Y2,R2,T2) where Q2 = I - Y2 T2 Y2^H
  211. *
  212. CALL CGELQT3( M2, N-M1, A( I1, I1 ), LDA,
  213. & T( I1, I1 ), LDT, IINFO )
  214. *
  215. * Compute T3 = T(J1:N1,1:N) = -T1 Y1^H Y2 T2
  216. *
  217. DO I=1,M2
  218. DO J=1,M1
  219. T( J, I+M1 ) = (A( J, I+M1 ))
  220. END DO
  221. END DO
  222. *
  223. CALL CTRMM( 'R', 'U', 'C', 'U', M1, M2, ONE,
  224. & A( I1, I1 ), LDA, T( 1, I1 ), LDT )
  225. *
  226. CALL CGEMM( 'N', 'C', M1, M2, N-M, ONE, A( 1, J1 ), LDA,
  227. & A( I1, J1 ), LDA, ONE, T( 1, I1 ), LDT )
  228. *
  229. CALL CTRMM( 'L', 'U', 'N', 'N', M1, M2, -ONE, T, LDT,
  230. & T( 1, I1 ), LDT )
  231. *
  232. CALL CTRMM( 'R', 'U', 'N', 'N', M1, M2, ONE,
  233. & T( I1, I1 ), LDT, T( 1, I1 ), LDT )
  234. *
  235. *
  236. *
  237. * Y = (Y1,Y2); L = [ L1 0 ]; T = [T1 T3]
  238. * [ A(1:N1,J1:N) L2 ] [ 0 T2]
  239. *
  240. END IF
  241. *
  242. RETURN
  243. *
  244. * End of CGELQT3
  245. *
  246. END