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