LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
ztpqrt.f
Go to the documentation of this file.
1*> \brief \b ZTPQRT
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZTPQRT + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ztpqrt.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ztpqrt.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztpqrt.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZTPQRT( M, N, L, NB, A, LDA, B, LDB, T, LDT, WORK,
20* INFO )
21*
22* .. Scalar Arguments ..
23* INTEGER INFO, LDA, LDB, LDT, N, M, L, NB
24* ..
25* .. Array Arguments ..
26* COMPLEX*16 A( LDA, * ), B( LDB, * ), T( LDT, * ), WORK( * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> ZTPQRT computes a blocked QR factorization of a complex
36*> "triangular-pentagonal" matrix C, which is composed of a
37*> triangular block A and pentagonal block B, using the compact
38*> WY representation for Q.
39*> \endverbatim
40*
41* Arguments:
42* ==========
43*
44*> \param[in] M
45*> \verbatim
46*> M is INTEGER
47*> The number of rows of the matrix B.
48*> M >= 0.
49*> \endverbatim
50*>
51*> \param[in] N
52*> \verbatim
53*> N is INTEGER
54*> The number of columns of the matrix B, and the order of the
55*> triangular matrix A.
56*> N >= 0.
57*> \endverbatim
58*>
59*> \param[in] L
60*> \verbatim
61*> L is INTEGER
62*> The number of rows of the upper trapezoidal part of B.
63*> MIN(M,N) >= L >= 0. See Further Details.
64*> \endverbatim
65*>
66*> \param[in] NB
67*> \verbatim
68*> NB is INTEGER
69*> The block size to be used in the blocked QR. N >= NB >= 1.
70*> \endverbatim
71*>
72*> \param[in,out] A
73*> \verbatim
74*> A is COMPLEX*16 array, dimension (LDA,N)
75*> On entry, the upper triangular N-by-N matrix A.
76*> On exit, the elements on and above the diagonal of the array
77*> contain the upper triangular matrix R.
78*> \endverbatim
79*>
80*> \param[in] LDA
81*> \verbatim
82*> LDA is INTEGER
83*> The leading dimension of the array A. LDA >= max(1,N).
84*> \endverbatim
85*>
86*> \param[in,out] B
87*> \verbatim
88*> B is COMPLEX*16 array, dimension (LDB,N)
89*> On entry, the pentagonal M-by-N matrix B. The first M-L rows
90*> are rectangular, and the last L rows are upper trapezoidal.
91*> On exit, B contains the pentagonal matrix V. See Further Details.
92*> \endverbatim
93*>
94*> \param[in] LDB
95*> \verbatim
96*> LDB is INTEGER
97*> The leading dimension of the array B. LDB >= max(1,M).
98*> \endverbatim
99*>
100*> \param[out] T
101*> \verbatim
102*> T is COMPLEX*16 array, dimension (LDT,N)
103*> The upper triangular block reflectors stored in compact form
104*> as a sequence of upper triangular blocks. See Further Details.
105*> \endverbatim
106*>
107*> \param[in] LDT
108*> \verbatim
109*> LDT is INTEGER
110*> The leading dimension of the array T. LDT >= NB.
111*> \endverbatim
112*>
113*> \param[out] WORK
114*> \verbatim
115*> WORK is COMPLEX*16 array, dimension (NB*N)
116*> \endverbatim
117*>
118*> \param[out] INFO
119*> \verbatim
120*> INFO is INTEGER
121*> = 0: successful exit
122*> < 0: if INFO = -i, the i-th argument had an illegal value
123*> \endverbatim
124*
125* Authors:
126* ========
127*
128*> \author Univ. of Tennessee
129*> \author Univ. of California Berkeley
130*> \author Univ. of Colorado Denver
131*> \author NAG Ltd.
132*
133*> \ingroup tpqrt
134*
135*> \par Further Details:
136* =====================
137*>
138*> \verbatim
139*>
140*> The input matrix C is a (N+M)-by-N matrix
141*>
142*> C = [ A ]
143*> [ B ]
144*>
145*> where A is an upper triangular N-by-N matrix, and B is M-by-N pentagonal
146*> matrix consisting of a (M-L)-by-N rectangular matrix B1 on top of a L-by-N
147*> upper trapezoidal matrix B2:
148*>
149*> B = [ B1 ] <- (M-L)-by-N rectangular
150*> [ B2 ] <- L-by-N upper trapezoidal.
151*>
152*> The upper trapezoidal matrix B2 consists of the first L rows of a
153*> N-by-N upper triangular matrix, where 0 <= L <= MIN(M,N). If L=0,
154*> B is rectangular M-by-N; if M=L=N, B is upper triangular.
155*>
156*> The matrix W stores the elementary reflectors H(i) in the i-th column
157*> below the diagonal (of A) in the (N+M)-by-N input matrix C
158*>
159*> C = [ A ] <- upper triangular N-by-N
160*> [ B ] <- M-by-N pentagonal
161*>
162*> so that W can be represented as
163*>
164*> W = [ I ] <- identity, N-by-N
165*> [ V ] <- M-by-N, same form as B.
166*>
167*> Thus, all of information needed for W is contained on exit in B, which
168*> we call V above. Note that V has the same form as B; that is,
169*>
170*> V = [ V1 ] <- (M-L)-by-N rectangular
171*> [ V2 ] <- L-by-N upper trapezoidal.
172*>
173*> The columns of V represent the vectors which define the H(i)'s.
174*>
175*> The number of blocks is B = ceiling(N/NB), where each
176*> block is of order NB except for the last block, which is of order
177*> IB = N - (B-1)*NB. For each of the B blocks, a upper triangular block
178*> reflector factor is computed: T1, T2, ..., TB. The NB-by-NB (and IB-by-IB
179*> for the last block) T's are stored in the NB-by-N matrix T as
180*>
181*> T = [T1 T2 ... TB].
182*> \endverbatim
183*>
184* =====================================================================
185 SUBROUTINE ztpqrt( M, N, L, NB, A, LDA, B, LDB, T, LDT, WORK,
186 $ INFO )
187*
188* -- LAPACK computational routine --
189* -- LAPACK is a software package provided by Univ. of Tennessee, --
190* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
191*
192* .. Scalar Arguments ..
193 INTEGER INFO, LDA, LDB, LDT, N, M, L, NB
194* ..
195* .. Array Arguments ..
196 COMPLEX*16 A( LDA, * ), B( LDB, * ), T( LDT, * ), WORK( * )
197* ..
198*
199* =====================================================================
200*
201* ..
202* .. Local Scalars ..
203 INTEGER I, IB, LB, MB, IINFO
204* ..
205* .. External Subroutines ..
206 EXTERNAL ztpqrt2, ztprfb, xerbla
207* ..
208* .. Executable Statements ..
209*
210* Test the input arguments
211*
212 info = 0
213 IF( m.LT.0 ) THEN
214 info = -1
215 ELSE IF( n.LT.0 ) THEN
216 info = -2
217 ELSE IF( l.LT.0 .OR. (l.GT.min(m,n) .AND. min(m,n).GE.0)) THEN
218 info = -3
219 ELSE IF( nb.LT.1 .OR. (nb.GT.n .AND. n.GT.0)) THEN
220 info = -4
221 ELSE IF( lda.LT.max( 1, n ) ) THEN
222 info = -6
223 ELSE IF( ldb.LT.max( 1, m ) ) THEN
224 info = -8
225 ELSE IF( ldt.LT.nb ) THEN
226 info = -10
227 END IF
228 IF( info.NE.0 ) THEN
229 CALL xerbla( 'ZTPQRT', -info )
230 RETURN
231 END IF
232*
233* Quick return if possible
234*
235 IF( m.EQ.0 .OR. n.EQ.0 ) RETURN
236*
237 DO i = 1, n, nb
238*
239* Compute the QR factorization of the current block
240*
241 ib = min( n-i+1, nb )
242 mb = min( m-l+i+ib-1, m )
243 IF( i.GE.l ) THEN
244 lb = 0
245 ELSE
246 lb = mb-m+l-i+1
247 END IF
248*
249 CALL ztpqrt2( mb, ib, lb, a(i,i), lda, b( 1, i ), ldb,
250 $ t(1, i ), ldt, iinfo )
251*
252* Update by applying H**H to B(:,I+IB:N) from the left
253*
254 IF( i+ib.LE.n ) THEN
255 CALL ztprfb( 'L', 'C', 'F', 'C', mb, n-i-ib+1, ib, lb,
256 $ b( 1, i ), ldb, t( 1, i ), ldt,
257 $ a( i, i+ib ), lda, b( 1, i+ib ), ldb,
258 $ work, ib )
259 END IF
260 END DO
261 RETURN
262*
263* End of ZTPQRT
264*
265 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine ztpqrt2(m, n, l, a, lda, b, ldb, t, ldt, info)
ZTPQRT2 computes a QR factorization of a real or complex "triangular-pentagonal" matrix,...
Definition ztpqrt2.f:171
subroutine ztpqrt(m, n, l, nb, a, lda, b, ldb, t, ldt, work, info)
ZTPQRT
Definition ztpqrt.f:187
subroutine ztprfb(side, trans, direct, storev, m, n, k, l, v, ldv, t, ldt, a, lda, b, ldb, work, ldwork)
ZTPRFB applies a complex "triangular-pentagonal" block reflector to a complex matrix,...
Definition ztprfb.f:249