LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
ctpmlqt.f
Go to the documentation of this file.
1*> \brief \b CTPMLQT
2*
3* Definition:
4* ===========
5*
6* SUBROUTINE CTPMLQT( SIDE, TRANS, M, N, K, L, MB, V, LDV, T, LDT,
7* A, LDA, B, LDB, WORK, INFO )
8*
9* .. Scalar Arguments ..
10* CHARACTER SIDE, TRANS
11* INTEGER INFO, K, LDV, LDA, LDB, M, N, L, MB, LDT
12* ..
13* .. Array Arguments ..
14* COMPLEX V( LDV, * ), A( LDA, * ), B( LDB, * ),
15* $ T( LDT, * ), WORK( * )
16* ..
17*
18*
19*> \par Purpose:
20* =============
21*>
22*> \verbatim
23*>
24*> CTPMLQT applies a complex unitary matrix Q obtained from a
25*> "triangular-pentagonal" complex block reflector H to a general
26*> complex matrix C, which consists of two blocks A and B.
27*> \endverbatim
28*
29* Arguments:
30* ==========
31*
32*> \param[in] SIDE
33*> \verbatim
34*> SIDE is CHARACTER*1
35*> = 'L': apply Q or Q**H from the Left;
36*> = 'R': apply Q or Q**H from the Right.
37*> \endverbatim
38*>
39*> \param[in] TRANS
40*> \verbatim
41*> TRANS is CHARACTER*1
42*> = 'N': No transpose, apply Q;
43*> = 'C': Conjugate transpose, apply Q**H.
44*> \endverbatim
45*>
46*> \param[in] M
47*> \verbatim
48*> M is INTEGER
49*> The number of rows of the matrix B. M >= 0.
50*> \endverbatim
51*>
52*> \param[in] N
53*> \verbatim
54*> N is INTEGER
55*> The number of columns of the matrix B. N >= 0.
56*> \endverbatim
57*>
58*> \param[in] K
59*> \verbatim
60*> K is INTEGER
61*> The number of elementary reflectors whose product defines
62*> the matrix Q.
63*> \endverbatim
64*>
65*> \param[in] L
66*> \verbatim
67*> L is INTEGER
68*> The order of the trapezoidal part of V.
69*> K >= L >= 0. See Further Details.
70*> \endverbatim
71*>
72*> \param[in] MB
73*> \verbatim
74*> MB is INTEGER
75*> The block size used for the storage of T. K >= MB >= 1.
76*> This must be the same value of MB used to generate T
77*> in CTPLQT.
78*> \endverbatim
79*>
80*> \param[in] V
81*> \verbatim
82*> V is COMPLEX array, dimension (LDV,K)
83*> The i-th row must contain the vector which defines the
84*> elementary reflector H(i), for i = 1,2,...,k, as returned by
85*> CTPLQT in B. See Further Details.
86*> \endverbatim
87*>
88*> \param[in] LDV
89*> \verbatim
90*> LDV is INTEGER
91*> The leading dimension of the array V. LDV >= K.
92*> \endverbatim
93*>
94*> \param[in] T
95*> \verbatim
96*> T is COMPLEX array, dimension (LDT,K)
97*> The upper triangular factors of the block reflectors
98*> as returned by CTPLQT, stored as a MB-by-K matrix.
99*> \endverbatim
100*>
101*> \param[in] LDT
102*> \verbatim
103*> LDT is INTEGER
104*> The leading dimension of the array T. LDT >= MB.
105*> \endverbatim
106*>
107*> \param[in,out] A
108*> \verbatim
109*> A is COMPLEX array, dimension
110*> (LDA,N) if SIDE = 'L' or
111*> (LDA,K) if SIDE = 'R'
112*> On entry, the K-by-N or M-by-K matrix A.
113*> On exit, A is overwritten by the corresponding block of
114*> Q*C or Q**H*C or C*Q or C*Q**H. See Further Details.
115*> \endverbatim
116*>
117*> \param[in] LDA
118*> \verbatim
119*> LDA is INTEGER
120*> The leading dimension of the array A.
121*> If SIDE = 'L', LDA >= max(1,K);
122*> If SIDE = 'R', LDA >= max(1,M).
123*> \endverbatim
124*>
125*> \param[in,out] B
126*> \verbatim
127*> B is COMPLEX array, dimension (LDB,N)
128*> On entry, the M-by-N matrix B.
129*> On exit, B is overwritten by the corresponding block of
130*> Q*C or Q**H*C or C*Q or C*Q**H. See Further Details.
131*> \endverbatim
132*>
133*> \param[in] LDB
134*> \verbatim
135*> LDB is INTEGER
136*> The leading dimension of the array B.
137*> LDB >= max(1,M).
138*> \endverbatim
139*>
140*> \param[out] WORK
141*> \verbatim
142*> WORK is COMPLEX array. The dimension of WORK is
143*> N*MB if SIDE = 'L', or M*MB if SIDE = 'R'.
144*> \endverbatim
145*>
146*> \param[out] INFO
147*> \verbatim
148*> INFO is INTEGER
149*> = 0: successful exit
150*> < 0: if INFO = -i, the i-th argument had an illegal value
151*> \endverbatim
152*
153* Authors:
154* ========
155*
156*> \author Univ. of Tennessee
157*> \author Univ. of California Berkeley
158*> \author Univ. of Colorado Denver
159*> \author NAG Ltd.
160*
161*> \ingroup tpmlqt
162*
163*> \par Further Details:
164* =====================
165*>
166*> \verbatim
167*>
168*> The columns of the pentagonal matrix V contain the elementary reflectors
169*> H(1), H(2), ..., H(K); V is composed of a rectangular block V1 and a
170*> trapezoidal block V2:
171*>
172*> V = [V1] [V2].
173*>
174*>
175*> The size of the trapezoidal block V2 is determined by the parameter L,
176*> where 0 <= L <= K; V2 is lower trapezoidal, consisting of the first L
177*> rows of a K-by-K upper triangular matrix. If L=K, V2 is lower triangular;
178*> if L=0, there is no trapezoidal block, hence V = V1 is rectangular.
179*>
180*> If SIDE = 'L': C = [A] where A is K-by-N, B is M-by-N and V is K-by-M.
181*> [B]
182*>
183*> If SIDE = 'R': C = [A B] where A is M-by-K, B is M-by-N and V is K-by-N.
184*>
185*> The complex unitary matrix Q is formed from V and T.
186*>
187*> If TRANS='N' and SIDE='L', C is on exit replaced with Q * C.
188*>
189*> If TRANS='C' and SIDE='L', C is on exit replaced with Q**H * C.
190*>
191*> If TRANS='N' and SIDE='R', C is on exit replaced with C * Q.
192*>
193*> If TRANS='C' and SIDE='R', C is on exit replaced with C * Q**H.
194*> \endverbatim
195*>
196* =====================================================================
197 SUBROUTINE ctpmlqt( SIDE, TRANS, M, N, K, L, MB, V, LDV, T,
198 $ LDT,
199 $ A, LDA, B, LDB, WORK, INFO )
200*
201* -- LAPACK computational routine --
202* -- LAPACK is a software package provided by Univ. of Tennessee, --
203* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
204*
205* .. Scalar Arguments ..
206 CHARACTER SIDE, TRANS
207 INTEGER INFO, K, LDV, LDA, LDB, M, N, L, MB, LDT
208* ..
209* .. Array Arguments ..
210 COMPLEX V( LDV, * ), A( LDA, * ), B( LDB, * ),
211 $ T( LDT, * ), WORK( * )
212* ..
213*
214* =====================================================================
215*
216* ..
217* .. Local Scalars ..
218 LOGICAL LEFT, RIGHT, TRAN, NOTRAN
219 INTEGER I, IB, NB, LB, KF, LDAQ
220* ..
221* .. External Functions ..
222 LOGICAL LSAME
223 EXTERNAL LSAME
224* ..
225* .. External Subroutines ..
226 EXTERNAL xerbla, ctprfb
227* ..
228* .. Intrinsic Functions ..
229 INTRINSIC max, min
230* ..
231* .. Executable Statements ..
232*
233* .. Test the input arguments ..
234*
235 info = 0
236 left = lsame( side, 'L' )
237 right = lsame( side, 'R' )
238 tran = lsame( trans, 'C' )
239 notran = lsame( trans, 'N' )
240*
241 IF ( left ) THEN
242 ldaq = max( 1, k )
243 ELSE IF ( right ) THEN
244 ldaq = max( 1, m )
245 END IF
246 IF( .NOT.left .AND. .NOT.right ) THEN
247 info = -1
248 ELSE IF( .NOT.tran .AND. .NOT.notran ) THEN
249 info = -2
250 ELSE IF( m.LT.0 ) THEN
251 info = -3
252 ELSE IF( n.LT.0 ) THEN
253 info = -4
254 ELSE IF( k.LT.0 ) THEN
255 info = -5
256 ELSE IF( l.LT.0 .OR. l.GT.k ) THEN
257 info = -6
258 ELSE IF( mb.LT.1 .OR. (mb.GT.k .AND. k.GT.0) ) THEN
259 info = -7
260 ELSE IF( ldv.LT.k ) THEN
261 info = -9
262 ELSE IF( ldt.LT.mb ) THEN
263 info = -11
264 ELSE IF( lda.LT.ldaq ) THEN
265 info = -13
266 ELSE IF( ldb.LT.max( 1, m ) ) THEN
267 info = -15
268 END IF
269*
270 IF( info.NE.0 ) THEN
271 CALL xerbla( 'CTPMLQT', -info )
272 RETURN
273 END IF
274*
275* .. Quick return if possible ..
276*
277 IF( m.EQ.0 .OR. n.EQ.0 .OR. k.EQ.0 ) RETURN
278*
279 IF( left .AND. notran ) THEN
280*
281 DO i = 1, k, mb
282 ib = min( mb, k-i+1 )
283 nb = min( m-l+i+ib-1, m )
284 IF( i.GE.l ) THEN
285 lb = 0
286 ELSE
287 lb = 0
288 END IF
289 CALL ctprfb( 'L', 'C', 'F', 'R', nb, n, ib, lb,
290 $ v( i, 1 ), ldv, t( 1, i ), ldt,
291 $ a( i, 1 ), lda, b, ldb, work, ib )
292 END DO
293*
294 ELSE IF( right .AND. tran ) THEN
295*
296 DO i = 1, k, mb
297 ib = min( mb, k-i+1 )
298 nb = min( n-l+i+ib-1, n )
299 IF( i.GE.l ) THEN
300 lb = 0
301 ELSE
302 lb = nb-n+l-i+1
303 END IF
304 CALL ctprfb( 'R', 'N', 'F', 'R', m, nb, ib, lb,
305 $ v( i, 1 ), ldv, t( 1, i ), ldt,
306 $ a( 1, i ), lda, b, ldb, work, m )
307 END DO
308*
309 ELSE IF( left .AND. tran ) THEN
310*
311 kf = ((k-1)/mb)*mb+1
312 DO i = kf, 1, -mb
313 ib = min( mb, k-i+1 )
314 nb = min( m-l+i+ib-1, m )
315 IF( i.GE.l ) THEN
316 lb = 0
317 ELSE
318 lb = 0
319 END IF
320 CALL ctprfb( 'L', 'N', 'F', 'R', nb, n, ib, lb,
321 $ v( i, 1 ), ldv, t( 1, i ), ldt,
322 $ a( i, 1 ), lda, b, ldb, work, ib )
323 END DO
324*
325 ELSE IF( right .AND. notran ) THEN
326*
327 kf = ((k-1)/mb)*mb+1
328 DO i = kf, 1, -mb
329 ib = min( mb, k-i+1 )
330 nb = min( n-l+i+ib-1, n )
331 IF( i.GE.l ) THEN
332 lb = 0
333 ELSE
334 lb = nb-n+l-i+1
335 END IF
336 CALL ctprfb( 'R', 'C', 'F', 'R', m, nb, ib, lb,
337 $ v( i, 1 ), ldv, t( 1, i ), ldt,
338 $ a( 1, i ), lda, b, ldb, work, m )
339 END DO
340*
341 END IF
342*
343 RETURN
344*
345* End of CTPMLQT
346*
347 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine ctpmlqt(side, trans, m, n, k, l, mb, v, ldv, t, ldt, a, lda, b, ldb, work, info)
CTPMLQT
Definition ctpmlqt.f:200
subroutine ctprfb(side, trans, direct, storev, m, n, k, l, v, ldv, t, ldt, a, lda, b, ldb, work, ldwork)
CTPRFB applies a complex "triangular-pentagonal" block reflector to a complex matrix,...
Definition ctprfb.f:249