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.

sgelqt3.f 6.6 kB

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