LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ ctpmlqt()

subroutine ctpmlqt ( character  side,
character  trans,
integer  m,
integer  n,
integer  k,
integer  l,
integer  mb,
complex, dimension( ldv, * )  v,
integer  ldv,
complex, dimension( ldt, * )  t,
integer  ldt,
complex, dimension( lda, * )  a,
integer  lda,
complex, dimension( ldb, * )  b,
integer  ldb,
complex, dimension( * )  work,
integer  info 
)

CTPMLQT

Purpose:
 CTPMLQT applies a complex unitary matrix Q obtained from a
 "triangular-pentagonal" complex block reflector H to a general
 complex matrix C, which consists of two blocks A and B.
Parameters
[in]SIDE
          SIDE is CHARACTER*1
          = 'L': apply Q or Q**H from the Left;
          = 'R': apply Q or Q**H from the Right.
[in]TRANS
          TRANS is CHARACTER*1
          = 'N':  No transpose, apply Q;
          = 'C':  Conjugate transpose, apply Q**H.
[in]M
          M is INTEGER
          The number of rows of the matrix B. M >= 0.
[in]N
          N is INTEGER
          The number of columns of the matrix B. N >= 0.
[in]K
          K is INTEGER
          The number of elementary reflectors whose product defines
          the matrix Q.
[in]L
          L is INTEGER
          The order of the trapezoidal part of V.
          K >= L >= 0.  See Further Details.
[in]MB
          MB is INTEGER
          The block size used for the storage of T.  K >= MB >= 1.
          This must be the same value of MB used to generate T
          in CTPLQT.
[in]V
          V is COMPLEX array, dimension (LDV,K)
          The i-th row must contain the vector which defines the
          elementary reflector H(i), for i = 1,2,...,k, as returned by
          CTPLQT in B.  See Further Details.
[in]LDV
          LDV is INTEGER
          The leading dimension of the array V. LDV >= K.
[in]T
          T is COMPLEX array, dimension (LDT,K)
          The upper triangular factors of the block reflectors
          as returned by CTPLQT, stored as a MB-by-K matrix.
[in]LDT
          LDT is INTEGER
          The leading dimension of the array T.  LDT >= MB.
[in,out]A
          A is COMPLEX array, dimension
          (LDA,N) if SIDE = 'L' or
          (LDA,K) if SIDE = 'R'
          On entry, the K-by-N or M-by-K matrix A.
          On exit, A is overwritten by the corresponding block of
          Q*C or Q**H*C or C*Q or C*Q**H.  See Further Details.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.
          If SIDE = 'L', LDA >= max(1,K);
          If SIDE = 'R', LDA >= max(1,M).
[in,out]B
          B is COMPLEX array, dimension (LDB,N)
          On entry, the M-by-N matrix B.
          On exit, B is overwritten by the corresponding block of
          Q*C or Q**H*C or C*Q or C*Q**H.  See Further Details.
[in]LDB
          LDB is INTEGER
          The leading dimension of the array B.
          LDB >= max(1,M).
[out]WORK
          WORK is COMPLEX array. The dimension of WORK is
           N*MB if SIDE = 'L', or  M*MB if SIDE = 'R'.
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0:  if INFO = -i, the i-th argument had an illegal value
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
  The columns of the pentagonal matrix V contain the elementary reflectors
  H(1), H(2), ..., H(K); V is composed of a rectangular block V1 and a
  trapezoidal block V2:

        V = [V1] [V2].


  The size of the trapezoidal block V2 is determined by the parameter L,
  where 0 <= L <= K; V2 is lower trapezoidal, consisting of the first L
  rows of a K-by-K upper triangular matrix.  If L=K, V2 is lower triangular;
  if L=0, there is no trapezoidal block, hence V = V1 is rectangular.

  If SIDE = 'L':  C = [A]  where A is K-by-N,  B is M-by-N and V is K-by-M.
                      [B]

  If SIDE = 'R':  C = [A B]  where A is M-by-K, B is M-by-N and V is K-by-N.

  The complex unitary matrix Q is formed from V and T.

  If TRANS='N' and SIDE='L', C is on exit replaced with Q * C.

  If TRANS='C' and SIDE='L', C is on exit replaced with Q**H * C.

  If TRANS='N' and SIDE='R', C is on exit replaced with C * Q.

  If TRANS='C' and SIDE='R', C is on exit replaced with C * Q**H.

Definition at line 197 of file ctpmlqt.f.

199*
200* -- LAPACK computational routine --
201* -- LAPACK is a software package provided by Univ. of Tennessee, --
202* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
203*
204* .. Scalar Arguments ..
205 CHARACTER SIDE, TRANS
206 INTEGER INFO, K, LDV, LDA, LDB, M, N, L, MB, LDT
207* ..
208* .. Array Arguments ..
209 COMPLEX V( LDV, * ), A( LDA, * ), B( LDB, * ),
210 $ T( LDT, * ), WORK( * )
211* ..
212*
213* =====================================================================
214*
215* ..
216* .. Local Scalars ..
217 LOGICAL LEFT, RIGHT, TRAN, NOTRAN
218 INTEGER I, IB, NB, LB, KF, LDAQ
219* ..
220* .. External Functions ..
221 LOGICAL LSAME
222 EXTERNAL lsame
223* ..
224* .. External Subroutines ..
225 EXTERNAL xerbla, ctprfb
226* ..
227* .. Intrinsic Functions ..
228 INTRINSIC max, min
229* ..
230* .. Executable Statements ..
231*
232* .. Test the input arguments ..
233*
234 info = 0
235 left = lsame( side, 'L' )
236 right = lsame( side, 'R' )
237 tran = lsame( trans, 'C' )
238 notran = lsame( trans, 'N' )
239*
240 IF ( left ) THEN
241 ldaq = max( 1, k )
242 ELSE IF ( right ) THEN
243 ldaq = max( 1, m )
244 END IF
245 IF( .NOT.left .AND. .NOT.right ) THEN
246 info = -1
247 ELSE IF( .NOT.tran .AND. .NOT.notran ) THEN
248 info = -2
249 ELSE IF( m.LT.0 ) THEN
250 info = -3
251 ELSE IF( n.LT.0 ) THEN
252 info = -4
253 ELSE IF( k.LT.0 ) THEN
254 info = -5
255 ELSE IF( l.LT.0 .OR. l.GT.k ) THEN
256 info = -6
257 ELSE IF( mb.LT.1 .OR. (mb.GT.k .AND. k.GT.0) ) THEN
258 info = -7
259 ELSE IF( ldv.LT.k ) THEN
260 info = -9
261 ELSE IF( ldt.LT.mb ) THEN
262 info = -11
263 ELSE IF( lda.LT.ldaq ) THEN
264 info = -13
265 ELSE IF( ldb.LT.max( 1, m ) ) THEN
266 info = -15
267 END IF
268*
269 IF( info.NE.0 ) THEN
270 CALL xerbla( 'CTPMLQT', -info )
271 RETURN
272 END IF
273*
274* .. Quick return if possible ..
275*
276 IF( m.EQ.0 .OR. n.EQ.0 .OR. k.EQ.0 ) RETURN
277*
278 IF( left .AND. notran ) THEN
279*
280 DO i = 1, k, mb
281 ib = min( mb, k-i+1 )
282 nb = min( m-l+i+ib-1, m )
283 IF( i.GE.l ) THEN
284 lb = 0
285 ELSE
286 lb = 0
287 END IF
288 CALL ctprfb( 'L', 'C', 'F', 'R', nb, n, ib, lb,
289 $ v( i, 1 ), ldv, t( 1, i ), ldt,
290 $ a( i, 1 ), lda, b, ldb, work, ib )
291 END DO
292*
293 ELSE IF( right .AND. tran ) THEN
294*
295 DO i = 1, k, mb
296 ib = min( mb, k-i+1 )
297 nb = min( n-l+i+ib-1, n )
298 IF( i.GE.l ) THEN
299 lb = 0
300 ELSE
301 lb = nb-n+l-i+1
302 END IF
303 CALL ctprfb( 'R', 'N', 'F', 'R', m, nb, ib, lb,
304 $ v( i, 1 ), ldv, t( 1, i ), ldt,
305 $ a( 1, i ), lda, b, ldb, work, m )
306 END DO
307*
308 ELSE IF( left .AND. tran ) THEN
309*
310 kf = ((k-1)/mb)*mb+1
311 DO i = kf, 1, -mb
312 ib = min( mb, k-i+1 )
313 nb = min( m-l+i+ib-1, m )
314 IF( i.GE.l ) THEN
315 lb = 0
316 ELSE
317 lb = 0
318 END IF
319 CALL ctprfb( 'L', 'N', 'F', 'R', nb, n, ib, lb,
320 $ v( i, 1 ), ldv, t( 1, i ), ldt,
321 $ a( i, 1 ), lda, b, ldb, work, ib )
322 END DO
323*
324 ELSE IF( right .AND. notran ) THEN
325*
326 kf = ((k-1)/mb)*mb+1
327 DO i = kf, 1, -mb
328 ib = min( mb, k-i+1 )
329 nb = min( n-l+i+ib-1, n )
330 IF( i.GE.l ) THEN
331 lb = 0
332 ELSE
333 lb = nb-n+l-i+1
334 END IF
335 CALL ctprfb( 'R', 'C', 'F', 'R', m, nb, ib, lb,
336 $ v( i, 1 ), ldv, t( 1, i ), ldt,
337 $ a( 1, i ), lda, b, ldb, work, m )
338 END DO
339*
340 END IF
341*
342 RETURN
343*
344* End of CTPMLQT
345*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine ctprfb(side, trans, direct, storev, m, n, k, l, v, ldv, t, ldt, a, lda, b, ldb, work, ldwork)
CTPRFB applies a complex "triangular-pentagonal" block reflector to a complex matrix,...
Definition ctprfb.f:251
Here is the call graph for this function:
Here is the caller graph for this function: