LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
dtpmqrt.f
Go to the documentation of this file.
1 *> \brief \b DTPMQRT
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download DTPMQRT + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dtpmqrt.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dtpmqrt.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dtpmqrt.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE DTPMQRT( SIDE, TRANS, M, N, K, L, NB, 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, NB, LDT
27 * ..
28 * .. Array Arguments ..
29 * DOUBLE PRECISION V( LDV, * ), A( LDA, * ), B( LDB, * ),
30 * $ T( LDT, * ), WORK( * )
31 * ..
32 *
33 *
34 *> \par Purpose:
35 * =============
36 *>
37 *> \verbatim
38 *>
39 *> DTPMQRT 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 *> = 'C': 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] NB
88 *> \verbatim
89 *> NB is INTEGER
90 *> The block size used for the storage of T. K >= NB >= 1.
91 *> This must be the same value of NB used to generate T
92 *> in CTPQRT.
93 *> \endverbatim
94 *>
95 *> \param[in] V
96 *> \verbatim
97 *> V is DOUBLE PRECISION array, dimension (LDA,K)
98 *> The i-th column must contain the vector which defines the
99 *> elementary reflector H(i), for i = 1,2,...,k, as returned by
100 *> CTPQRT 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.
107 *> If SIDE = 'L', LDV >= max(1,M);
108 *> if SIDE = 'R', LDV >= max(1,N).
109 *> \endverbatim
110 *>
111 *> \param[in] T
112 *> \verbatim
113 *> T is DOUBLE PRECISION array, dimension (LDT,K)
114 *> The upper triangular factors of the block reflectors
115 *> as returned by CTPQRT, stored as a NB-by-K matrix.
116 *> \endverbatim
117 *>
118 *> \param[in] LDT
119 *> \verbatim
120 *> LDT is INTEGER
121 *> The leading dimension of the array T. LDT >= NB.
122 *> \endverbatim
123 *>
124 *> \param[in,out] A
125 *> \verbatim
126 *> A is DOUBLE PRECISION array, dimension
127 *> (LDA,N) if SIDE = 'L' or
128 *> (LDA,K) if SIDE = 'R'
129 *> On entry, the K-by-N or M-by-K matrix A.
130 *> On exit, A is overwritten by the corresponding block of
131 *> Q*C or Q**T*C or C*Q or C*Q**T. See Further Details.
132 *> \endverbatim
133 *>
134 *> \param[in] LDA
135 *> \verbatim
136 *> LDA is INTEGER
137 *> The leading dimension of the array A.
138 *> If SIDE = 'L', LDC >= max(1,K);
139 *> If SIDE = 'R', LDC >= max(1,M).
140 *> \endverbatim
141 *>
142 *> \param[in,out] B
143 *> \verbatim
144 *> B is DOUBLE PRECISION array, dimension (LDB,N)
145 *> On entry, the M-by-N matrix B.
146 *> On exit, B is overwritten by the corresponding block of
147 *> Q*C or Q**T*C or C*Q or C*Q**T. See Further Details.
148 *> \endverbatim
149 *>
150 *> \param[in] LDB
151 *> \verbatim
152 *> LDB is INTEGER
153 *> The leading dimension of the array B.
154 *> LDB >= max(1,M).
155 *> \endverbatim
156 *>
157 *> \param[out] WORK
158 *> \verbatim
159 *> WORK is DOUBLE PRECISION array. The dimension of WORK is
160 *> N*NB if SIDE = 'L', or M*NB if SIDE = 'R'.
161 *> \endverbatim
162 *>
163 *> \param[out] INFO
164 *> \verbatim
165 *> INFO is INTEGER
166 *> = 0: successful exit
167 *> < 0: if INFO = -i, the i-th argument had an illegal value
168 *> \endverbatim
169 *
170 * Authors:
171 * ========
172 *
173 *> \author Univ. of Tennessee
174 *> \author Univ. of California Berkeley
175 *> \author Univ. of Colorado Denver
176 *> \author NAG Ltd.
177 *
178 *> \date April 2012
179 *
180 *> \ingroup doubleOTHERcomputational
181 *
182 *> \par Further Details:
183 * =====================
184 *>
185 *> \verbatim
186 *>
187 *> The columns of the pentagonal matrix V contain the elementary reflectors
188 *> H(1), H(2), ..., H(K); V is composed of a rectangular block V1 and a
189 *> trapezoidal block V2:
190 *>
191 *> V = [V1]
192 *> [V2].
193 *>
194 *> The size of the trapezoidal block V2 is determined by the parameter L,
195 *> where 0 <= L <= K; V2 is upper trapezoidal, consisting of the first L
196 *> rows of a K-by-K upper triangular matrix. If L=K, V2 is upper triangular;
197 *> if L=0, there is no trapezoidal block, hence V = V1 is rectangular.
198 *>
199 *> If SIDE = 'L': C = [A] where A is K-by-N, B is M-by-N and V is M-by-K.
200 *> [B]
201 *>
202 *> If SIDE = 'R': C = [A B] where A is M-by-K, B is M-by-N and V is N-by-K.
203 *>
204 *> The real orthogonal matrix Q is formed from V and T.
205 *>
206 *> If TRANS='N' and SIDE='L', C is on exit replaced with Q * C.
207 *>
208 *> If TRANS='T' and SIDE='L', C is on exit replaced with Q**T * C.
209 *>
210 *> If TRANS='N' and SIDE='R', C is on exit replaced with C * Q.
211 *>
212 *> If TRANS='T' and SIDE='R', C is on exit replaced with C * Q**T.
213 *> \endverbatim
214 *>
215 * =====================================================================
216  SUBROUTINE dtpmqrt( SIDE, TRANS, M, N, K, L, NB, V, LDV, T, LDT,
217  $ a, lda, b, ldb, work, info )
218 *
219 * -- LAPACK computational routine (version 3.4.1) --
220 * -- LAPACK is a software package provided by Univ. of Tennessee, --
221 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
222 * April 2012
223 *
224 * .. Scalar Arguments ..
225  CHARACTER side, trans
226  INTEGER info, k, ldv, lda, ldb, m, n, l, nb, ldt
227 * ..
228 * .. Array Arguments ..
229  DOUBLE PRECISION v( ldv, * ), a( lda, * ), b( ldb, * ),
230  $ t( ldt, * ), work( * )
231 * ..
232 *
233 * =====================================================================
234 *
235 * ..
236 * .. Local Scalars ..
237  LOGICAL left, right, tran, notran
238  INTEGER i, ib, mb, lb, kf, q
239 * ..
240 * .. External Functions ..
241  LOGICAL lsame
242  EXTERNAL lsame
243 * ..
244 * .. External Subroutines ..
245  EXTERNAL xerbla, dlarfb
246 * ..
247 * .. Intrinsic Functions ..
248  INTRINSIC max, min
249 * ..
250 * .. Executable Statements ..
251 *
252 * .. Test the input arguments ..
253 *
254  info = 0
255  left = lsame( side, 'L' )
256  right = lsame( side, 'R' )
257  tran = lsame( trans, 'T' )
258  notran = lsame( trans, 'N' )
259 *
260  IF( left ) THEN
261  q = m
262  ELSE IF ( right ) THEN
263  q = n
264  END IF
265  IF( .NOT.left .AND. .NOT.right ) THEN
266  info = -1
267  ELSE IF( .NOT.tran .AND. .NOT.notran ) THEN
268  info = -2
269  ELSE IF( m.LT.0 ) THEN
270  info = -3
271  ELSE IF( n.LT.0 ) THEN
272  info = -4
273  ELSE IF( k.LT.0 ) THEN
274  info = -5
275  ELSE IF( l.LT.0 .OR. l.GT.k ) THEN
276  info = -6
277  ELSE IF( nb.LT.1 .OR. nb.GT.k ) THEN
278  info = -7
279  ELSE IF( ldv.LT.max( 1, q ) ) THEN
280  info = -9
281  ELSE IF( ldt.LT.nb ) THEN
282  info = -11
283  ELSE IF( lda.LT.max( 1, m ) ) THEN
284  info = -13
285  ELSE IF( ldb.LT.max( 1, m ) ) THEN
286  info = -15
287  END IF
288 *
289  IF( info.NE.0 ) THEN
290  CALL xerbla( 'DTPMQRT', -info )
291  return
292  END IF
293 *
294 * .. Quick return if possible ..
295 *
296  IF( m.EQ.0 .OR. n.EQ.0 .OR. k.EQ.0 ) return
297 *
298  IF( left .AND. tran ) THEN
299 *
300  DO i = 1, k, nb
301  ib = min( nb, k-i+1 )
302  mb = min( m-l+i+ib-1, m )
303  IF( i.GE.l ) THEN
304  lb = 0
305  ELSE
306  lb = mb-m+l-i+1
307  END IF
308  CALL dtprfb( 'L', 'T', 'F', 'C', mb, n, ib, lb,
309  $ v( 1, i ), ldv, t( 1, i ), ldt,
310  $ a( i, 1 ), lda, b, ldb, work, ib )
311  END DO
312 *
313  ELSE IF( right .AND. notran ) THEN
314 *
315  DO i = 1, k, nb
316  ib = min( nb, k-i+1 )
317  mb = min( n-l+i+ib-1, n )
318  IF( i.GE.l ) THEN
319  lb = 0
320  ELSE
321  lb = mb-n+l-i+1
322  END IF
323  CALL dtprfb( 'R', 'N', 'F', 'C', m, mb, ib, lb,
324  $ v( 1, i ), ldv, t( 1, i ), ldt,
325  $ a( 1, i ), lda, b, ldb, work, m )
326  END DO
327 *
328  ELSE IF( left .AND. notran ) THEN
329 *
330  kf = ((k-1)/nb)*nb+1
331  DO i = kf, 1, -nb
332  ib = min( nb, k-i+1 )
333  mb = min( m-l+i+ib-1, m )
334  IF( i.GE.l ) THEN
335  lb = 0
336  ELSE
337  lb = mb-m+l-i+1
338  END IF
339  CALL dtprfb( 'L', 'N', 'F', 'C', mb, n, ib, lb,
340  $ v( 1, i ), ldv, t( 1, i ), ldt,
341  $ a( i, 1 ), lda, b, ldb, work, ib )
342  END DO
343 *
344  ELSE IF( right .AND. tran ) THEN
345 *
346  kf = ((k-1)/nb)*nb+1
347  DO i = kf, 1, -nb
348  ib = min( nb, k-i+1 )
349  mb = min( n-l+i+ib-1, n )
350  IF( i.GE.l ) THEN
351  lb = 0
352  ELSE
353  lb = mb-n+l-i+1
354  END IF
355  CALL dtprfb( 'R', 'T', 'F', 'C', m, mb, ib, lb,
356  $ v( 1, i ), ldv, t( 1, i ), ldt,
357  $ a( 1, i ), lda, b, ldb, work, m )
358  END DO
359 *
360  END IF
361 *
362  return
363 *
364 * End of DTPMQRT
365 *
366  END