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