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