LAPACK  3.9.0
LAPACK: Linear Algebra PACKage
clamtsqr.f
Go to the documentation of this file.
1 *> \brief \b CLAMTSQR
2 *
3 * Definition:
4 * ===========
5 *
6 * SUBROUTINE CLAMTSQR( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
7 * $ LDT, C, LDC, WORK, LWORK, INFO )
8 *
9 *
10 * .. Scalar Arguments ..
11 * CHARACTER SIDE, TRANS
12 * INTEGER INFO, LDA, M, N, K, MB, NB, LDT, LWORK, LDC
13 * ..
14 * .. Array Arguments ..
15 * COMPLEX A( LDA, * ), WORK( * ), C(LDC, * ),
16 * $ T( LDT, * )
17 *> \par Purpose:
18 * =============
19 *>
20 *> \verbatim
21 *>
22 *> CLAMTSQR overwrites the general complex M-by-N matrix C with
23 *>
24 *>
25 *> SIDE = 'L' SIDE = 'R'
26 *> TRANS = 'N': Q * C C * Q
27 *> TRANS = 'C': Q**H * C C * Q**H
28 *> where Q is a real orthogonal matrix defined as the product
29 *> of blocked elementary reflectors computed by tall skinny
30 *> QR factorization (CLATSQR)
31 *> \endverbatim
32 *
33 * Arguments:
34 * ==========
35 *
36 *> \param[in] SIDE
37 *> \verbatim
38 *> SIDE is CHARACTER*1
39 *> = 'L': apply Q or Q**H from the Left;
40 *> = 'R': apply Q or Q**H from the Right.
41 *> \endverbatim
42 *>
43 *> \param[in] TRANS
44 *> \verbatim
45 *> TRANS is CHARACTER*1
46 *> = 'N': No transpose, apply Q;
47 *> = 'C': Conjugate Transpose, apply Q**H.
48 *> \endverbatim
49 *>
50 *> \param[in] M
51 *> \verbatim
52 *> M is INTEGER
53 *> The number of rows of the matrix A. M >=0.
54 *> \endverbatim
55 *>
56 *> \param[in] N
57 *> \verbatim
58 *> N is INTEGER
59 *> The number of columns of the matrix C. M >= N >= 0.
60 *> \endverbatim
61 *>
62 *> \param[in] K
63 *> \verbatim
64 *> K is INTEGER
65 *> The number of elementary reflectors whose product defines
66 *> the matrix Q.
67 *> N >= K >= 0;
68 *>
69 *> \endverbatim
70 *>
71 *> \param[in] MB
72 *> \verbatim
73 *> MB is INTEGER
74 *> The block size to be used in the blocked QR.
75 *> MB > N. (must be the same as DLATSQR)
76 *> \endverbatim
77 *>
78 *> \param[in] NB
79 *> \verbatim
80 *> NB is INTEGER
81 *> The column block size to be used in the blocked QR.
82 *> N >= NB >= 1.
83 *> \endverbatim
84 *>
85 *> \param[in] A
86 *> \verbatim
87 *> A is COMPLEX array, dimension (LDA,K)
88 *> The i-th column must contain the vector which defines the
89 *> blockedelementary reflector H(i), for i = 1,2,...,k, as
90 *> returned by DLATSQR in the first k columns of
91 *> its array argument A.
92 *> \endverbatim
93 *>
94 *> \param[in] LDA
95 *> \verbatim
96 *> LDA is INTEGER
97 *> The leading dimension of the array A.
98 *> If SIDE = 'L', LDA >= max(1,M);
99 *> if SIDE = 'R', LDA >= max(1,N).
100 *> \endverbatim
101 *>
102 *> \param[in] T
103 *> \verbatim
104 *> T is COMPLEX array, dimension
105 *> ( N * Number of blocks(CEIL(M-K/MB-K)),
106 *> The blocked upper triangular block reflectors stored in compact form
107 *> as a sequence of upper triangular blocks. See below
108 *> for further details.
109 *> \endverbatim
110 *>
111 *> \param[in] LDT
112 *> \verbatim
113 *> LDT is INTEGER
114 *> The leading dimension of the array T. LDT >= NB.
115 *> \endverbatim
116 *>
117 *> \param[in,out] C
118 *> \verbatim
119 *> C is COMPLEX array, dimension (LDC,N)
120 *> On entry, the M-by-N matrix C.
121 *> On exit, C is overwritten by Q*C or Q**H*C or C*Q**H or C*Q.
122 *> \endverbatim
123 *>
124 *> \param[in] LDC
125 *> \verbatim
126 *> LDC is INTEGER
127 *> The leading dimension of the array C. LDC >= max(1,M).
128 *> \endverbatim
129 *>
130 *> \param[out] WORK
131 *> \verbatim
132 *> (workspace) COMPLEX array, dimension (MAX(1,LWORK))
133 *>
134 *> \endverbatim
135 *> \param[in] LWORK
136 *> \verbatim
137 *> LWORK is INTEGER
138 *> The dimension of the array WORK.
139 *>
140 *> If SIDE = 'L', LWORK >= max(1,N)*NB;
141 *> if SIDE = 'R', LWORK >= max(1,MB)*NB.
142 *> If LWORK = -1, then a workspace query is assumed; the routine
143 *> only calculates the optimal size of the WORK array, returns
144 *> this value as the first entry of the WORK array, and no error
145 *> message related to LWORK is issued by XERBLA.
146 *>
147 *> \endverbatim
148 *> \param[out] INFO
149 *> \verbatim
150 *> INFO is INTEGER
151 *> = 0: successful exit
152 *> < 0: if INFO = -i, the i-th argument had an illegal value
153 *> \endverbatim
154 *
155 * Authors:
156 * ========
157 *
158 *> \author Univ. of Tennessee
159 *> \author Univ. of California Berkeley
160 *> \author Univ. of Colorado Denver
161 *> \author NAG Ltd.
162 *
163 *> \par Further Details:
164 * =====================
165 *>
166 *> \verbatim
167 *> Tall-Skinny QR (TSQR) performs QR by a sequence of orthogonal transformations,
168 *> representing Q as a product of other orthogonal matrices
169 *> Q = Q(1) * Q(2) * . . . * Q(k)
170 *> where each Q(i) zeros out subdiagonal entries of a block of MB rows of A:
171 *> Q(1) zeros out the subdiagonal entries of rows 1:MB of A
172 *> Q(2) zeros out the bottom MB-N rows of rows [1:N,MB+1:2*MB-N] of A
173 *> Q(3) zeros out the bottom MB-N rows of rows [1:N,2*MB-N+1:3*MB-2*N] of A
174 *> . . .
175 *>
176 *> Q(1) is computed by GEQRT, which represents Q(1) by Householder vectors
177 *> stored under the diagonal of rows 1:MB of A, and by upper triangular
178 *> block reflectors, stored in array T(1:LDT,1:N).
179 *> For more information see Further Details in GEQRT.
180 *>
181 *> Q(i) for i>1 is computed by TPQRT, which represents Q(i) by Householder vectors
182 *> stored in rows [(i-1)*(MB-N)+N+1:i*(MB-N)+N] of A, and by upper triangular
183 *> block reflectors, stored in array T(1:LDT,(i-1)*N+1:i*N).
184 *> The last Q(k) may use fewer rows.
185 *> For more information see Further Details in TPQRT.
186 *>
187 *> For more details of the overall algorithm, see the description of
188 *> Sequential TSQR in Section 2.2 of [1].
189 *>
190 *> [1] “Communication-Optimal Parallel and Sequential QR and LU Factorizations,”
191 *> J. Demmel, L. Grigori, M. Hoemmen, J. Langou,
192 *> SIAM J. Sci. Comput, vol. 34, no. 1, 2012
193 *> \endverbatim
194 *>
195 * =====================================================================
196  SUBROUTINE clamtsqr( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
197  $ LDT, C, LDC, WORK, LWORK, INFO )
198 *
199 * -- LAPACK computational routine (version 3.7.1) --
200 * -- LAPACK is a software package provided by Univ. of Tennessee, --
201 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
202 * June 2017
203 *
204 * .. Scalar Arguments ..
205  CHARACTER SIDE, TRANS
206  INTEGER INFO, LDA, M, N, K, MB, NB, LDT, LWORK, LDC
207 * ..
208 * .. Array Arguments ..
209  COMPLEX A( LDA, * ), WORK( * ), C(LDC, * ),
210  $ t( ldt, * )
211 * ..
212 *
213 * =====================================================================
214 *
215 * ..
216 * .. Local Scalars ..
217  LOGICAL LEFT, RIGHT, TRAN, NOTRAN, LQUERY
218  INTEGER I, II, KK, LW, CTR
219 * ..
220 * .. External Functions ..
221  LOGICAL LSAME
222  EXTERNAL lsame
223 * .. External Subroutines ..
224  EXTERNAL cgemqrt, ctpmqrt, xerbla
225 * ..
226 * .. Executable Statements ..
227 *
228 * Test the input arguments
229 *
230  lquery = lwork.LT.0
231  notran = lsame( trans, 'N' )
232  tran = lsame( trans, 'C' )
233  left = lsame( side, 'L' )
234  right = lsame( side, 'R' )
235  IF (left) THEN
236  lw = n * nb
237  ELSE
238  lw = m * nb
239  END IF
240 *
241  info = 0
242  IF( .NOT.left .AND. .NOT.right ) THEN
243  info = -1
244  ELSE IF( .NOT.tran .AND. .NOT.notran ) THEN
245  info = -2
246  ELSE IF( m.LT.0 ) THEN
247  info = -3
248  ELSE IF( n.LT.0 ) THEN
249  info = -4
250  ELSE IF( k.LT.0 ) THEN
251  info = -5
252  ELSE IF( lda.LT.max( 1, k ) ) THEN
253  info = -9
254  ELSE IF( ldt.LT.max( 1, nb) ) THEN
255  info = -11
256  ELSE IF( ldc.LT.max( 1, m ) ) THEN
257  info = -13
258  ELSE IF(( lwork.LT.max(1,lw)).AND.(.NOT.lquery)) THEN
259  info = -15
260  END IF
261 *
262 * Determine the block size if it is tall skinny or short and wide
263 *
264  IF( info.EQ.0) THEN
265  work(1) = lw
266  END IF
267 *
268  IF( info.NE.0 ) THEN
269  CALL xerbla( 'CLAMTSQR', -info )
270  RETURN
271  ELSE IF (lquery) THEN
272  RETURN
273  END IF
274 *
275 * Quick return if possible
276 *
277  IF( min(m,n,k).EQ.0 ) THEN
278  RETURN
279  END IF
280 *
281  IF((mb.LE.k).OR.(mb.GE.max(m,n,k))) THEN
282  CALL cgemqrt( side, trans, m, n, k, nb, a, lda,
283  $ t, ldt, c, ldc, work, info)
284  RETURN
285  END IF
286 *
287  IF(left.AND.notran) THEN
288 *
289 * Multiply Q to the last block of C
290 *
291  kk = mod((m-k),(mb-k))
292  ctr = (m-k)/(mb-k)
293  IF (kk.GT.0) THEN
294  ii=m-kk+1
295  CALL ctpmqrt('L','N',kk , n, k, 0, nb, a(ii,1), lda,
296  $ t(1, ctr*k+1),ldt , c(1,1), ldc,
297  $ c(ii,1), ldc, work, info )
298  ELSE
299  ii=m+1
300  END IF
301 *
302  DO i=ii-(mb-k),mb+1,-(mb-k)
303 *
304 * Multiply Q to the current block of C (I:I+MB,1:N)
305 *
306  ctr = ctr - 1
307  CALL ctpmqrt('L','N',mb-k , n, k, 0,nb, a(i,1), lda,
308  $ t(1,ctr*k+1),ldt, c(1,1), ldc,
309  $ c(i,1), ldc, work, info )
310 
311  END DO
312 *
313 * Multiply Q to the first block of C (1:MB,1:N)
314 *
315  CALL cgemqrt('L','N',mb , n, k, nb, a(1,1), lda, t
316  $ ,ldt ,c(1,1), ldc, work, info )
317 *
318  ELSE IF (left.AND.tran) THEN
319 *
320 * Multiply Q to the first block of C
321 *
322  kk = mod((m-k),(mb-k))
323  ii=m-kk+1
324  ctr = 1
325  CALL cgemqrt('L','C',mb , n, k, nb, a(1,1), lda, t
326  $ ,ldt ,c(1,1), ldc, work, info )
327 *
328  DO i=mb+1,ii-mb+k,(mb-k)
329 *
330 * Multiply Q to the current block of C (I:I+MB,1:N)
331 *
332  CALL ctpmqrt('L','C',mb-k , n, k, 0,nb, a(i,1), lda,
333  $ t(1, ctr*k+1),ldt, c(1,1), ldc,
334  $ c(i,1), ldc, work, info )
335  ctr = ctr + 1
336 *
337  END DO
338  IF(ii.LE.m) THEN
339 *
340 * Multiply Q to the last block of C
341 *
342  CALL ctpmqrt('L','C',kk , n, k, 0,nb, a(ii,1), lda,
343  $ t(1,ctr*k+1), ldt, c(1,1), ldc,
344  $ c(ii,1), ldc, work, info )
345 *
346  END IF
347 *
348  ELSE IF(right.AND.tran) THEN
349 *
350 * Multiply Q to the last block of C
351 *
352  kk = mod((n-k),(mb-k))
353  ctr = (n-k)/(mb-k)
354  IF (kk.GT.0) THEN
355  ii=n-kk+1
356  CALL ctpmqrt('R','C',m , kk, k, 0, nb, a(ii,1), lda,
357  $ t(1, ctr*k+1), ldt, c(1,1), ldc,
358  $ c(1,ii), ldc, work, info )
359  ELSE
360  ii=n+1
361  END IF
362 *
363  DO i=ii-(mb-k),mb+1,-(mb-k)
364 *
365 * Multiply Q to the current block of C (1:M,I:I+MB)
366 *
367  ctr = ctr - 1
368  CALL ctpmqrt('R','C',m , mb-k, k, 0,nb, a(i,1), lda,
369  $ t(1,ctr*k+1), ldt, c(1,1), ldc,
370  $ c(1,i), ldc, work, info )
371  END DO
372 *
373 * Multiply Q to the first block of C (1:M,1:MB)
374 *
375  CALL cgemqrt('R','C',m , mb, k, nb, a(1,1), lda, t
376  $ ,ldt ,c(1,1), ldc, work, info )
377 *
378  ELSE IF (right.AND.notran) THEN
379 *
380 * Multiply Q to the first block of C
381 *
382  kk = mod((n-k),(mb-k))
383  ii=n-kk+1
384  ctr = 1
385  CALL cgemqrt('R','N', m, mb , k, nb, a(1,1), lda, t
386  $ ,ldt ,c(1,1), ldc, work, info )
387 *
388  DO i=mb+1,ii-mb+k,(mb-k)
389 *
390 * Multiply Q to the current block of C (1:M,I:I+MB)
391 *
392  CALL ctpmqrt('R','N', m, mb-k, k, 0,nb, a(i,1), lda,
393  $ t(1,ctr*k+1),ldt, c(1,1), ldc,
394  $ c(1,i), ldc, work, info )
395  ctr = ctr + 1
396 *
397  END DO
398  IF(ii.LE.n) THEN
399 *
400 * Multiply Q to the last block of C
401 *
402  CALL ctpmqrt('R','N', m, kk , k, 0,nb, a(ii,1), lda,
403  $ t(1,ctr*k+1),ldt, c(1,1), ldc,
404  $ c(1,ii), ldc, work, info )
405 *
406  END IF
407 *
408  END IF
409 *
410  work(1) = lw
411  RETURN
412 *
413 * End of CLAMTSQR
414 *
415  END
ctpmqrt
subroutine ctpmqrt(SIDE, TRANS, M, N, K, L, NB, V, LDV, T, LDT, A, LDA, B, LDB, WORK, INFO)
CTPMQRT
Definition: ctpmqrt.f:218
clamtsqr
subroutine clamtsqr(SIDE, TRANS, M, N, K, MB, NB, A, LDA, T, LDT, C, LDC, WORK, LWORK, INFO)
CLAMTSQR
Definition: clamtsqr.f:198
xerbla
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
cgemqrt
subroutine cgemqrt(SIDE, TRANS, M, N, K, NB, V, LDV, T, LDT, C, LDC, WORK, INFO)
CGEMQRT
Definition: cgemqrt.f:170