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

◆ cgemqrt()

subroutine cgemqrt ( character  side,
character  trans,
integer  m,
integer  n,
integer  k,
integer  nb,
complex, dimension( ldv, * )  v,
integer  ldv,
complex, dimension( ldt, * )  t,
integer  ldt,
complex, dimension( ldc, * )  c,
integer  ldc,
complex, dimension( * )  work,
integer  info 
)

CGEMQRT

Download CGEMQRT + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 CGEMQRT overwrites the general complex M-by-N matrix C with

                 SIDE = 'L'     SIDE = 'R'
 TRANS = 'N':      Q C            C Q
 TRANS = 'C':    Q**H C            C Q**H

 where Q is a complex orthogonal matrix defined as the product of K
 elementary reflectors:

       Q = H(1) H(2) . . . H(K) = I - V T V**H

 generated using the compact WY representation as returned by CGEQRT.

 Q is of order M if SIDE = 'L' and of order N  if SIDE = 'R'.
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 C. M >= 0.
[in]N
          N is INTEGER
          The number of columns of the matrix C. N >= 0.
[in]K
          K is INTEGER
          The number of elementary reflectors whose product defines
          the matrix Q.
          If SIDE = 'L', M >= K >= 0;
          if SIDE = 'R', N >= K >= 0.
[in]NB
          NB is INTEGER
          The block size used for the storage of T.  K >= NB >= 1.
          This must be the same value of NB used to generate T
          in CGEQRT.
[in]V
          V is COMPLEX array, dimension (LDV,K)
          The i-th column must contain the vector which defines the
          elementary reflector H(i), for i = 1,2,...,k, as returned by
          CGEQRT in the first K columns of its array argument A.
[in]LDV
          LDV is INTEGER
          The leading dimension of the array V.
          If SIDE = 'L', LDA >= max(1,M);
          if SIDE = 'R', LDA >= max(1,N).
[in]T
          T is COMPLEX array, dimension (LDT,K)
          The upper triangular factors of the block reflectors
          as returned by CGEQRT, stored as a NB-by-N matrix.
[in]LDT
          LDT is INTEGER
          The leading dimension of the array T.  LDT >= NB.
[in,out]C
          C is COMPLEX array, dimension (LDC,N)
          On entry, the M-by-N matrix C.
          On exit, C is overwritten by Q C, Q**H C, C Q**H or C Q.
[in]LDC
          LDC is INTEGER
          The leading dimension of the array C. LDC >= max(1,M).
[out]WORK
          WORK is COMPLEX array. The dimension of WORK is
           N*NB if SIDE = 'L', or  M*NB 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.

Definition at line 166 of file cgemqrt.f.

168*
169* -- LAPACK computational routine --
170* -- LAPACK is a software package provided by Univ. of Tennessee, --
171* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
172*
173* .. Scalar Arguments ..
174 CHARACTER SIDE, TRANS
175 INTEGER INFO, K, LDV, LDC, M, N, NB, LDT
176* ..
177* .. Array Arguments ..
178 COMPLEX V( LDV, * ), C( LDC, * ), T( LDT, * ), WORK( * )
179* ..
180*
181* =====================================================================
182*
183* ..
184* .. Local Scalars ..
185 LOGICAL LEFT, RIGHT, TRAN, NOTRAN
186 INTEGER I, IB, LDWORK, KF, Q
187* ..
188* .. External Functions ..
189 LOGICAL LSAME
190 EXTERNAL lsame
191* ..
192* .. External Subroutines ..
193 EXTERNAL xerbla, clarfb
194* ..
195* .. Intrinsic Functions ..
196 INTRINSIC max, min
197* ..
198* .. Executable Statements ..
199*
200* .. Test the input arguments ..
201*
202 info = 0
203 left = lsame( side, 'L' )
204 right = lsame( side, 'R' )
205 tran = lsame( trans, 'C' )
206 notran = lsame( trans, 'N' )
207*
208 IF( left ) THEN
209 ldwork = max( 1, n )
210 q = m
211 ELSE IF ( right ) THEN
212 ldwork = max( 1, m )
213 q = n
214 END IF
215 IF( .NOT.left .AND. .NOT.right ) THEN
216 info = -1
217 ELSE IF( .NOT.tran .AND. .NOT.notran ) THEN
218 info = -2
219 ELSE IF( m.LT.0 ) THEN
220 info = -3
221 ELSE IF( n.LT.0 ) THEN
222 info = -4
223 ELSE IF( k.LT.0 .OR. k.GT.q ) THEN
224 info = -5
225 ELSE IF( nb.LT.1 .OR. (nb.GT.k .AND. k.GT.0)) THEN
226 info = -6
227 ELSE IF( ldv.LT.max( 1, q ) ) THEN
228 info = -8
229 ELSE IF( ldt.LT.nb ) THEN
230 info = -10
231 ELSE IF( ldc.LT.max( 1, m ) ) THEN
232 info = -12
233 END IF
234*
235 IF( info.NE.0 ) THEN
236 CALL xerbla( 'CGEMQRT', -info )
237 RETURN
238 END IF
239*
240* .. Quick return if possible ..
241*
242 IF( m.EQ.0 .OR. n.EQ.0 .OR. k.EQ.0 ) RETURN
243*
244 IF( left .AND. tran ) THEN
245*
246 DO i = 1, k, nb
247 ib = min( nb, k-i+1 )
248 CALL clarfb( 'L', 'C', 'F', 'C', m-i+1, n, ib,
249 $ v( i, i ), ldv, t( 1, i ), ldt,
250 $ c( i, 1 ), ldc, work, ldwork )
251 END DO
252*
253 ELSE IF( right .AND. notran ) THEN
254*
255 DO i = 1, k, nb
256 ib = min( nb, k-i+1 )
257 CALL clarfb( 'R', 'N', 'F', 'C', m, n-i+1, ib,
258 $ v( i, i ), ldv, t( 1, i ), ldt,
259 $ c( 1, i ), ldc, work, ldwork )
260 END DO
261*
262 ELSE IF( left .AND. notran ) THEN
263*
264 kf = ((k-1)/nb)*nb+1
265 DO i = kf, 1, -nb
266 ib = min( nb, k-i+1 )
267 CALL clarfb( 'L', 'N', 'F', 'C', m-i+1, n, ib,
268 $ v( i, i ), ldv, t( 1, i ), ldt,
269 $ c( i, 1 ), ldc, work, ldwork )
270 END DO
271*
272 ELSE IF( right .AND. tran ) THEN
273*
274 kf = ((k-1)/nb)*nb+1
275 DO i = kf, 1, -nb
276 ib = min( nb, k-i+1 )
277 CALL clarfb( 'R', 'C', 'F', 'C', m, n-i+1, ib,
278 $ v( i, i ), ldv, t( 1, i ), ldt,
279 $ c( 1, i ), ldc, work, ldwork )
280 END DO
281*
282 END IF
283*
284 RETURN
285*
286* End of CGEMQRT
287*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine clarfb(side, trans, direct, storev, m, n, k, v, ldv, t, ldt, c, ldc, work, ldwork)
CLARFB applies a block reflector or its conjugate-transpose to a general rectangular matrix.
Definition clarfb.f:197
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: