4 * SUBROUTINE CTPLQT( M, N, L, MB, A, LDA, B, LDB, T, LDT, WORK,
7 * .. Scalar Arguments ..
8 * INTEGER INFO, LDA, LDB, LDT, N, M, L, MB
10 * .. Array Arguments ..
11 * COMPLEX A( LDA, * ), B( LDB, * ), T( LDT, * ), WORK( * )
20 *> CTPLQT computes a blocked LQ factorization of a complex
21 *> "triangular-pentagonal" matrix C, which is composed of a
22 *> triangular block A and pentagonal block B, using the compact
23 *> WY representation for Q.
32 *> The number of rows of the matrix B, and the order of the
33 *> triangular matrix A.
40 *> The number of columns of the matrix B.
47 *> The number of rows of the lower trapezoidal part of B.
48 *> MIN(M,N) >= L >= 0. See Further Details.
54 *> The block size to be used in the blocked QR. M >= MB >= 1.
59 *> A is COMPLEX array, dimension (LDA,N)
60 *> On entry, the lower triangular N-by-N matrix A.
61 *> On exit, the elements on and below the diagonal of the array
62 *> contain the lower triangular matrix L.
68 *> The leading dimension of the array A. LDA >= max(1,N).
73 *> B is COMPLEX array, dimension (LDB,N)
74 *> On entry, the pentagonal M-by-N matrix B. The first N-L columns
75 *> are rectangular, and the last L columns are lower trapezoidal.
76 *> On exit, B contains the pentagonal matrix V. See Further Details.
82 *> The leading dimension of the array B. LDB >= max(1,M).
87 *> T is COMPLEX array, dimension (LDT,N)
88 *> The lower triangular block reflectors stored in compact form
89 *> as a sequence of upper triangular blocks. See Further Details.
95 *> The leading dimension of the array T. LDT >= MB.
100 *> WORK is COMPLEX array, dimension (MB*M)
106 *> = 0: successful exit
107 *> < 0: if INFO = -i, the i-th argument had an illegal value
113 *> \author Univ. of Tennessee
114 *> \author Univ. of California Berkeley
115 *> \author Univ. of Colorado Denver
118 *> \date November 2013
120 *> \ingroup doubleOTHERcomputational
122 *> \par Further Details:
123 * =====================
127 *> The input matrix C is a M-by-(M+N) matrix
132 *> where A is an lower triangular N-by-N matrix, and B is M-by-N pentagonal
133 *> matrix consisting of a M-by-(N-L) rectangular matrix B1 on left of a M-by-L
134 *> upper trapezoidal matrix B2:
135 *> [ B ] = [ B1 ] [ B2 ]
136 *> [ B1 ] <- M-by-(N-L) rectangular
137 *> [ B2 ] <- M-by-L upper trapezoidal.
139 *> The lower trapezoidal matrix B2 consists of the first L columns of a
140 *> N-by-N lower triangular matrix, where 0 <= L <= MIN(M,N). If L=0,
141 *> B is rectangular M-by-N; if M=L=N, B is lower triangular.
143 *> The matrix W stores the elementary reflectors H(i) in the i-th row
144 *> above the diagonal (of A) in the M-by-(M+N) input matrix C
145 *> [ C ] = [ A ] [ B ]
146 *> [ A ] <- lower triangular N-by-N
147 *> [ B ] <- M-by-N pentagonal
149 *> so that W can be represented as
150 *> [ W ] = [ I ] [ V ]
151 *> [ I ] <- identity, N-by-N
152 *> [ V ] <- M-by-N, same form as B.
154 *> Thus, all of information needed for W is contained on exit in B, which
155 *> we call V above. Note that V has the same form as B; that is,
156 *> [ V ] = [ V1 ] [ V2 ]
157 *> [ V1 ] <- M-by-(N-L) rectangular
158 *> [ V2 ] <- M-by-L lower trapezoidal.
160 *> The rows of V represent the vectors which define the H(i)'s.
162 *> The number of blocks is B = ceiling(M/MB), where each
163 *> block is of order MB except for the last block, which is of order
164 *> IB = M - (M-1)*MB. For each of the B blocks, a upper triangular block
165 *> reflector factor is computed: T1, T2, ..., TB. The MB-by-MB (and IB-by-IB
166 *> for the last block) T's are stored in the MB-by-N matrix T as
168 *> T = [T1 T2 ... TB].
171 * =====================================================================
172 SUBROUTINE CTPLQT( M, N, L, MB, A, LDA, B, LDB, T, LDT, WORK,
175 * -- LAPACK computational routine (version 3.5.0) --
176 * -- LAPACK is a software package provided by Univ. of Tennessee, --
177 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
180 * .. Scalar Arguments ..
181 INTEGER INFO, LDA, LDB, LDT, N, M, L, MB
183 * .. Array Arguments ..
184 COMPLEX A( LDA, * ), B( LDB, * ), T( LDT, * ), WORK( * )
187 * =====================================================================
190 * .. Local Scalars ..
191 INTEGER I, IB, LB, NB, IINFO
193 * .. External Subroutines ..
194 EXTERNAL CTPLQT2, CTPRFB, XERBLA
196 * .. Executable Statements ..
198 * Test the input arguments
203 ELSE IF( N.LT.0 ) THEN
205 ELSE IF( L.LT.0 .OR. (L.GT.MIN(M,N) .AND. MIN(M,N).GE.0)) THEN
207 ELSE IF( MB.LT.1 .OR. (MB.GT.M .AND. M.GT.0)) THEN
209 ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
211 ELSE IF( LDB.LT.MAX( 1, M ) ) THEN
213 ELSE IF( LDT.LT.MB ) THEN
217 CALL XERBLA( 'CTPLQT', -INFO )
221 * Quick return if possible
223 IF( M.EQ.0 .OR. N.EQ.0 ) RETURN
227 * Compute the QR factorization of the current block
229 IB = MIN( M-I+1, MB )
230 NB = MIN( N-L+I+IB-1, N )
237 CALL CTPLQT2( IB, NB, LB, A(I,I), LDA, B( I, 1 ), LDB,
238 $ T(1, I ), LDT, IINFO )
240 * Update by applying H**T to B(I+IB:M,:) from the right
243 CALL CTPRFB( 'R', 'N', 'F', 'R', M-I-IB+1, NB, IB, LB,
244 $ B( I, 1 ), LDB, T( 1, I ), LDT,
245 $ A( I+IB, I ), LDA, B( I+IB, 1 ), LDB,