LAPACK  3.9.0
LAPACK: Linear Algebra PACKage
ctplqt2.f
Go to the documentation of this file.
1 *> \brief \b CTPLQT2
2 *
3 * Definition:
4 * ===========
5 *
6 * SUBROUTINE CTPLQT2( M, N, L, A, LDA, B, LDB, T, LDT, INFO )
7 *
8 * .. Scalar Arguments ..
9 * INTEGER INFO, LDA, LDB, LDT, N, M, L
10 * ..
11 * .. Array Arguments ..
12 * COMPLEX A( LDA, * ), B( LDB, * ), T( LDT, * )
13 * ..
14 *
15 *
16 *> \par Purpose:
17 * =============
18 *>
19 *> \verbatim
20 *>
21 *> CTPLQT2 computes a LQ a factorization of a complex "triangular-pentagonal"
22 *> matrix C, which is composed of a triangular block A and pentagonal block B,
23 *> using the compact WY representation for Q.
24 *> \endverbatim
25 *
26 * Arguments:
27 * ==========
28 *
29 *> \param[in] M
30 *> \verbatim
31 *> M is INTEGER
32 *> The total number of rows of the matrix B.
33 *> M >= 0.
34 *> \endverbatim
35 *>
36 *> \param[in] N
37 *> \verbatim
38 *> N is INTEGER
39 *> The number of columns of the matrix B, and the order of
40 *> the triangular matrix A.
41 *> N >= 0.
42 *> \endverbatim
43 *>
44 *> \param[in] L
45 *> \verbatim
46 *> L is INTEGER
47 *> The number of rows of the lower trapezoidal part of B.
48 *> MIN(M,N) >= L >= 0. See Further Details.
49 *> \endverbatim
50 *>
51 *> \param[in,out] A
52 *> \verbatim
53 *> A is COMPLEX array, dimension (LDA,M)
54 *> On entry, the lower triangular M-by-M matrix A.
55 *> On exit, the elements on and below the diagonal of the array
56 *> contain the lower triangular matrix L.
57 *> \endverbatim
58 *>
59 *> \param[in] LDA
60 *> \verbatim
61 *> LDA is INTEGER
62 *> The leading dimension of the array A. LDA >= max(1,M).
63 *> \endverbatim
64 *>
65 *> \param[in,out] B
66 *> \verbatim
67 *> B is COMPLEX array, dimension (LDB,N)
68 *> On entry, the pentagonal M-by-N matrix B. The first N-L columns
69 *> are rectangular, and the last L columns are lower trapezoidal.
70 *> On exit, B contains the pentagonal matrix V. See Further Details.
71 *> \endverbatim
72 *>
73 *> \param[in] LDB
74 *> \verbatim
75 *> LDB is INTEGER
76 *> The leading dimension of the array B. LDB >= max(1,M).
77 *> \endverbatim
78 *>
79 *> \param[out] T
80 *> \verbatim
81 *> T is COMPLEX array, dimension (LDT,M)
82 *> The N-by-N upper triangular factor T of the block reflector.
83 *> See Further Details.
84 *> \endverbatim
85 *>
86 *> \param[in] LDT
87 *> \verbatim
88 *> LDT is INTEGER
89 *> The leading dimension of the array T. LDT >= max(1,M)
90 *> \endverbatim
91 *>
92 *> \param[out] INFO
93 *> \verbatim
94 *> INFO is INTEGER
95 *> = 0: successful exit
96 *> < 0: if INFO = -i, the i-th argument had an illegal value
97 *> \endverbatim
98 *
99 * Authors:
100 * ========
101 *
102 *> \author Univ. of Tennessee
103 *> \author Univ. of California Berkeley
104 *> \author Univ. of Colorado Denver
105 *> \author NAG Ltd.
106 *
107 *> \date June 2017
108 *
109 *> \ingroup doubleOTHERcomputational
110 *
111 *> \par Further Details:
112 * =====================
113 *>
114 *> \verbatim
115 *>
116 *> The input matrix C is a M-by-(M+N) matrix
117 *>
118 *> C = [ A ][ B ]
119 *>
120 *>
121 *> where A is an lower triangular M-by-M matrix, and B is M-by-N pentagonal
122 *> matrix consisting of a M-by-(N-L) rectangular matrix B1 left of a M-by-L
123 *> upper trapezoidal matrix B2:
124 *>
125 *> B = [ B1 ][ B2 ]
126 *> [ B1 ] <- M-by-(N-L) rectangular
127 *> [ B2 ] <- M-by-L lower trapezoidal.
128 *>
129 *> The lower trapezoidal matrix B2 consists of the first L columns of a
130 *> N-by-N lower triangular matrix, where 0 <= L <= MIN(M,N). If L=0,
131 *> B is rectangular M-by-N; if M=L=N, B is lower triangular.
132 *>
133 *> The matrix W stores the elementary reflectors H(i) in the i-th row
134 *> above the diagonal (of A) in the M-by-(M+N) input matrix C
135 *>
136 *> C = [ A ][ B ]
137 *> [ A ] <- lower triangular M-by-M
138 *> [ B ] <- M-by-N pentagonal
139 *>
140 *> so that W can be represented as
141 *>
142 *> W = [ I ][ V ]
143 *> [ I ] <- identity, M-by-M
144 *> [ V ] <- M-by-N, same form as B.
145 *>
146 *> Thus, all of information needed for W is contained on exit in B, which
147 *> we call V above. Note that V has the same form as B; that is,
148 *>
149 *> W = [ V1 ][ V2 ]
150 *> [ V1 ] <- M-by-(N-L) rectangular
151 *> [ V2 ] <- M-by-L lower trapezoidal.
152 *>
153 *> The rows of V represent the vectors which define the H(i)'s.
154 *> The (M+N)-by-(M+N) block reflector H is then given by
155 *>
156 *> H = I - W**T * T * W
157 *>
158 *> where W^H is the conjugate transpose of W and T is the upper triangular
159 *> factor of the block reflector.
160 *> \endverbatim
161 *>
162 * =====================================================================
163  SUBROUTINE ctplqt2( M, N, L, A, LDA, B, LDB, T, LDT, INFO )
164 *
165 * -- LAPACK computational routine (version 3.7.1) --
166 * -- LAPACK is a software package provided by Univ. of Tennessee, --
167 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
168 * June 2017
169 *
170 * .. Scalar Arguments ..
171  INTEGER INFO, LDA, LDB, LDT, N, M, L
172 * ..
173 * .. Array Arguments ..
174  COMPLEX A( LDA, * ), B( LDB, * ), T( LDT, * )
175 * ..
176 *
177 * =====================================================================
178 *
179 * .. Parameters ..
180  COMPLEX ONE, ZERO
181  parameter( zero = ( 0.0e+0, 0.0e+0 ),one = ( 1.0e+0, 0.0e+0 ) )
182 * ..
183 * .. Local Scalars ..
184  INTEGER I, J, P, MP, NP
185  COMPLEX ALPHA
186 * ..
187 * .. External Subroutines ..
188  EXTERNAL clarfg, cgemv, cgerc, ctrmv, xerbla
189 * ..
190 * .. Intrinsic Functions ..
191  INTRINSIC max, min
192 * ..
193 * .. Executable Statements ..
194 *
195 * Test the input arguments
196 *
197  info = 0
198  IF( m.LT.0 ) THEN
199  info = -1
200  ELSE IF( n.LT.0 ) THEN
201  info = -2
202  ELSE IF( l.LT.0 .OR. l.GT.min(m,n) ) THEN
203  info = -3
204  ELSE IF( lda.LT.max( 1, m ) ) THEN
205  info = -5
206  ELSE IF( ldb.LT.max( 1, m ) ) THEN
207  info = -7
208  ELSE IF( ldt.LT.max( 1, m ) ) THEN
209  info = -9
210  END IF
211  IF( info.NE.0 ) THEN
212  CALL xerbla( 'CTPLQT2', -info )
213  RETURN
214  END IF
215 *
216 * Quick return if possible
217 *
218  IF( n.EQ.0 .OR. m.EQ.0 ) RETURN
219 *
220  DO i = 1, m
221 *
222 * Generate elementary reflector H(I) to annihilate B(I,:)
223 *
224  p = n-l+min( l, i )
225  CALL clarfg( p+1, a( i, i ), b( i, 1 ), ldb, t( 1, i ) )
226  t(1,i)=conjg(t(1,i))
227  IF( i.LT.m ) THEN
228  DO j = 1, p
229  b( i, j ) = conjg(b(i,j))
230  END DO
231 *
232 * W(M-I:1) := C(I+1:M,I:N) * C(I,I:N) [use W = T(M,:)]
233 *
234  DO j = 1, m-i
235  t( m, j ) = (a( i+j, i ))
236  END DO
237  CALL cgemv( 'N', m-i, p, one, b( i+1, 1 ), ldb,
238  $ b( i, 1 ), ldb, one, t( m, 1 ), ldt )
239 *
240 * C(I+1:M,I:N) = C(I+1:M,I:N) + alpha * C(I,I:N)*W(M-1:1)^H
241 *
242  alpha = -(t( 1, i ))
243  DO j = 1, m-i
244  a( i+j, i ) = a( i+j, i ) + alpha*(t( m, j ))
245  END DO
246  CALL cgerc( m-i, p, (alpha), t( m, 1 ), ldt,
247  $ b( i, 1 ), ldb, b( i+1, 1 ), ldb )
248  DO j = 1, p
249  b( i, j ) = conjg(b(i,j))
250  END DO
251  END IF
252  END DO
253 *
254  DO i = 2, m
255 *
256 * T(I,1:I-1) := C(I:I-1,1:N)**H * (alpha * C(I,I:N))
257 *
258  alpha = -(t( 1, i ))
259  DO j = 1, i-1
260  t( i, j ) = zero
261  END DO
262  p = min( i-1, l )
263  np = min( n-l+1, n )
264  mp = min( p+1, m )
265  DO j = 1, n-l+p
266  b(i,j)=conjg(b(i,j))
267  END DO
268 *
269 * Triangular part of B2
270 *
271  DO j = 1, p
272  t( i, j ) = (alpha*b( i, n-l+j ))
273  END DO
274  CALL ctrmv( 'L', 'N', 'N', p, b( 1, np ), ldb,
275  $ t( i, 1 ), ldt )
276 *
277 * Rectangular part of B2
278 *
279  CALL cgemv( 'N', i-1-p, l, alpha, b( mp, np ), ldb,
280  $ b( i, np ), ldb, zero, t( i,mp ), ldt )
281 *
282 * B1
283 
284 *
285  CALL cgemv( 'N', i-1, n-l, alpha, b, ldb, b( i, 1 ), ldb,
286  $ one, t( i, 1 ), ldt )
287 *
288 
289 *
290 * T(1:I-1,I) := T(1:I-1,1:I-1) * T(I,1:I-1)
291 *
292  DO j = 1, i-1
293  t(i,j)=conjg(t(i,j))
294  END DO
295  CALL ctrmv( 'L', 'C', 'N', i-1, t, ldt, t( i, 1 ), ldt )
296  DO j = 1, i-1
297  t(i,j)=conjg(t(i,j))
298  END DO
299  DO j = 1, n-l+p
300  b(i,j)=conjg(b(i,j))
301  END DO
302 *
303 * T(I,I) = tau(I)
304 *
305  t( i, i ) = t( 1, i )
306  t( 1, i ) = zero
307  END DO
308  DO i=1,m
309  DO j= i+1,m
310  t(i,j)=(t(j,i))
311  t(j,i)=zero
312  END DO
313  END DO
314 
315 *
316 * End of CTPLQT2
317 *
318  END
clarfg
subroutine clarfg(N, ALPHA, X, INCX, TAU)
CLARFG generates an elementary reflector (Householder matrix).
Definition: clarfg.f:108
cgemv
subroutine cgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
CGEMV
Definition: cgemv.f:160
cgerc
subroutine cgerc(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)
CGERC
Definition: cgerc.f:132
ctrmv
subroutine ctrmv(UPLO, TRANS, DIAG, N, A, LDA, X, INCX)
CTRMV
Definition: ctrmv.f:149
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