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