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.

claswlq.f 7.5 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262
  1. *
  2. * Definition:
  3. * ===========
  4. *
  5. * SUBROUTINE CLASWLQ( M, N, MB, NB, A, LDA, T, LDT, WORK,
  6. * LWORK, INFO)
  7. *
  8. * .. Scalar Arguments ..
  9. * INTEGER INFO, LDA, M, N, MB, NB, LDT, LWORK
  10. * ..
  11. * .. Array Arguments ..
  12. * COMPLEX A( LDA, * ), T( LDT, * ), WORK( * )
  13. * ..
  14. *
  15. *
  16. *> \par Purpose:
  17. * =============
  18. *>
  19. *> \verbatim
  20. *>
  21. *> CLASWLQ computes a blocked Short-Wide LQ factorization of a
  22. *> M-by-N matrix A, where N >= M:
  23. *> A = L * Q
  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 >= 0.
  33. *> \endverbatim
  34. *>
  35. *> \param[in] N
  36. *> \verbatim
  37. *> N is INTEGER
  38. *> The number of columns of the matrix A. N >= M >= 0.
  39. *> \endverbatim
  40. *>
  41. *> \param[in] MB
  42. *> \verbatim
  43. *> MB is INTEGER
  44. *> The row block size to be used in the blocked QR.
  45. *> M >= MB >= 1
  46. *> \endverbatim
  47. *> \param[in] NB
  48. *> \verbatim
  49. *> NB is INTEGER
  50. *> The column block size to be used in the blocked QR.
  51. *> NB > M.
  52. *> \endverbatim
  53. *>
  54. *> \param[in,out] A
  55. *> \verbatim
  56. *> A is COMPLEX array, dimension (LDA,N)
  57. *> On entry, the M-by-N matrix A.
  58. *> On exit, the elements on and below the diagonal
  59. *> of the array contain the N-by-N lower triangular matrix L;
  60. *> the elements above the diagonal represent Q by the rows
  61. *> of blocked V (see Further Details).
  62. *>
  63. *> \endverbatim
  64. *>
  65. *> \param[in] LDA
  66. *> \verbatim
  67. *> LDA is INTEGER
  68. *> The leading dimension of the array A. LDA >= max(1,M).
  69. *> \endverbatim
  70. *>
  71. *> \param[out] T
  72. *> \verbatim
  73. *> T is COMPLEX array,
  74. *> dimension (LDT, N * Number_of_row_blocks)
  75. *> where Number_of_row_blocks = CEIL((N-M)/(NB-M))
  76. *> The blocked upper triangular block reflectors stored in compact form
  77. *> as a sequence of upper triangular blocks.
  78. *> See Further Details below.
  79. *> \endverbatim
  80. *>
  81. *> \param[in] LDT
  82. *> \verbatim
  83. *> LDT is INTEGER
  84. *> The leading dimension of the array T. LDT >= MB.
  85. *> \endverbatim
  86. *>
  87. *>
  88. *> \param[out] WORK
  89. *> \verbatim
  90. *> (workspace) COMPLEX array, dimension (MAX(1,LWORK))
  91. *>
  92. *> \endverbatim
  93. *> \param[in] LWORK
  94. *> \verbatim
  95. *> The dimension of the array WORK. LWORK >= MB*M.
  96. *> If LWORK = -1, then a workspace query is assumed; the routine
  97. *> only calculates the optimal size of the WORK array, returns
  98. *> this value as the first entry of the WORK array, and no error
  99. *> message related to LWORK is issued by XERBLA.
  100. *>
  101. *> \endverbatim
  102. *> \param[out] INFO
  103. *> \verbatim
  104. *> INFO is INTEGER
  105. *> = 0: successful exit
  106. *> < 0: if INFO = -i, the i-th argument had an illegal value
  107. *> \endverbatim
  108. *
  109. * Authors:
  110. * ========
  111. *
  112. *> \author Univ. of Tennessee
  113. *> \author Univ. of California Berkeley
  114. *> \author Univ. of Colorado Denver
  115. *> \author NAG Ltd.
  116. *
  117. *> \par Further Details:
  118. * =====================
  119. *>
  120. *> \verbatim
  121. *> Short-Wide LQ (SWLQ) performs LQ by a sequence of orthogonal transformations,
  122. *> representing Q as a product of other orthogonal matrices
  123. *> Q = Q(1) * Q(2) * . . . * Q(k)
  124. *> where each Q(i) zeros out upper diagonal entries of a block of NB rows of A:
  125. *> Q(1) zeros out the upper diagonal entries of rows 1:NB of A
  126. *> Q(2) zeros out the bottom MB-N rows of rows [1:M,NB+1:2*NB-M] of A
  127. *> Q(3) zeros out the bottom MB-N rows of rows [1:M,2*NB-M+1:3*NB-2*M] of A
  128. *> . . .
  129. *>
  130. *> Q(1) is computed by GELQT, which represents Q(1) by Householder vectors
  131. *> stored under the diagonal of rows 1:MB of A, and by upper triangular
  132. *> block reflectors, stored in array T(1:LDT,1:N).
  133. *> For more information see Further Details in GELQT.
  134. *>
  135. *> Q(i) for i>1 is computed by TPLQT, which represents Q(i) by Householder vectors
  136. *> stored in columns [(i-1)*(NB-M)+M+1:i*(NB-M)+M] of A, and by upper triangular
  137. *> block reflectors, stored in array T(1:LDT,(i-1)*M+1:i*M).
  138. *> The last Q(k) may use fewer rows.
  139. *> For more information see Further Details in TPQRT.
  140. *>
  141. *> For more details of the overall algorithm, see the description of
  142. *> Sequential TSQR in Section 2.2 of [1].
  143. *>
  144. *> [1] “Communication-Optimal Parallel and Sequential QR and LU Factorizations,”
  145. *> J. Demmel, L. Grigori, M. Hoemmen, J. Langou,
  146. *> SIAM J. Sci. Comput, vol. 34, no. 1, 2012
  147. *> \endverbatim
  148. *>
  149. * =====================================================================
  150. SUBROUTINE CLASWLQ( M, N, MB, NB, A, LDA, T, LDT, WORK, LWORK,
  151. $ INFO)
  152. *
  153. * -- LAPACK computational routine (version 3.7.1) --
  154. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  155. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd. --
  156. * June 2017
  157. *
  158. * .. Scalar Arguments ..
  159. INTEGER INFO, LDA, M, N, MB, NB, LWORK, LDT
  160. * ..
  161. * .. Array Arguments ..
  162. COMPLEX A( LDA, * ), WORK( * ), T( LDT, *)
  163. * ..
  164. *
  165. * =====================================================================
  166. *
  167. * ..
  168. * .. Local Scalars ..
  169. LOGICAL LQUERY
  170. INTEGER I, II, KK, CTR
  171. * ..
  172. * .. EXTERNAL FUNCTIONS ..
  173. LOGICAL LSAME
  174. EXTERNAL LSAME
  175. * .. EXTERNAL SUBROUTINES ..
  176. EXTERNAL CGELQT, CTPLQT, XERBLA
  177. * .. INTRINSIC FUNCTIONS ..
  178. INTRINSIC MAX, MIN, MOD
  179. * ..
  180. * .. EXTERNAL FUNCTIONS ..
  181. INTEGER ILAENV
  182. EXTERNAL ILAENV
  183. * ..
  184. * .. EXECUTABLE STATEMENTS ..
  185. *
  186. * TEST THE INPUT ARGUMENTS
  187. *
  188. INFO = 0
  189. *
  190. LQUERY = ( LWORK.EQ.-1 )
  191. *
  192. IF( M.LT.0 ) THEN
  193. INFO = -1
  194. ELSE IF( N.LT.0 .OR. N.LT.M ) THEN
  195. INFO = -2
  196. ELSE IF( MB.LT.1 .OR. ( MB.GT.M .AND. M.GT.0 )) THEN
  197. INFO = -3
  198. ELSE IF( NB.LE.M ) THEN
  199. INFO = -4
  200. ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
  201. INFO = -5
  202. ELSE IF( LDT.LT.MB ) THEN
  203. INFO = -8
  204. ELSE IF( ( LWORK.LT.M*MB) .AND. (.NOT.LQUERY) ) THEN
  205. INFO = -10
  206. END IF
  207. IF( INFO.EQ.0) THEN
  208. WORK(1) = MB*M
  209. END IF
  210. *
  211. IF( INFO.NE.0 ) THEN
  212. CALL XERBLA( 'CLASWLQ', -INFO )
  213. RETURN
  214. ELSE IF (LQUERY) THEN
  215. RETURN
  216. END IF
  217. *
  218. * Quick return if possible
  219. *
  220. IF( MIN(M,N).EQ.0 ) THEN
  221. RETURN
  222. END IF
  223. *
  224. * The LQ Decomposition
  225. *
  226. IF((M.GE.N).OR.(NB.LE.M).OR.(NB.GE.N)) THEN
  227. CALL CGELQT( M, N, MB, A, LDA, T, LDT, WORK, INFO)
  228. RETURN
  229. END IF
  230. *
  231. KK = MOD((N-M),(NB-M))
  232. II=N-KK+1
  233. *
  234. * Compute the LQ factorization of the first block A(1:M,1:NB)
  235. *
  236. CALL CGELQT( M, NB, MB, A(1,1), LDA, T, LDT, WORK, INFO)
  237. CTR = 1
  238. *
  239. DO I = NB+1, II-NB+M , (NB-M)
  240. *
  241. * Compute the QR factorization of the current block A(1:M,I:I+NB-M)
  242. *
  243. CALL CTPLQT( M, NB-M, 0, MB, A(1,1), LDA, A( 1, I ),
  244. $ LDA, T(1,CTR*M+1),
  245. $ LDT, WORK, INFO )
  246. CTR = CTR + 1
  247. END DO
  248. *
  249. * Compute the QR factorization of the last block A(1:M,II:N)
  250. *
  251. IF (II.LE.N) THEN
  252. CALL CTPLQT( M, KK, 0, MB, A(1,1), LDA, A( 1, II ),
  253. $ LDA, T(1,CTR*M+1), LDT,
  254. $ WORK, INFO )
  255. END IF
  256. *
  257. WORK( 1 ) = M * MB
  258. RETURN
  259. *
  260. * End of CLASWLQ
  261. *
  262. END