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

◆ cunmlq()

subroutine cunmlq ( character  side,
character  trans,
integer  m,
integer  n,
integer  k,
complex, dimension( lda, * )  a,
integer  lda,
complex, dimension( * )  tau,
complex, dimension( ldc, * )  c,
integer  ldc,
complex, dimension( * )  work,
integer  lwork,
integer  info 
)

CUNMLQ

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

Purpose:
 CUNMLQ 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 unitary matrix defined as the product of k
 elementary reflectors

       Q = H(k)**H . . . H(2)**H H(1)**H

 as returned by CGELQF. 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]A
          A is COMPLEX array, dimension
                               (LDA,M) if SIDE = 'L',
                               (LDA,N) if SIDE = 'R'
          The i-th row must contain the vector which defines the
          elementary reflector H(i), for i = 1,2,...,k, as returned by
          CGELQF in the first k rows of its array argument A.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A. LDA >= max(1,K).
[in]TAU
          TAU is COMPLEX array, dimension (K)
          TAU(i) must contain the scalar factor of the elementary
          reflector H(i), as returned by CGELQF.
[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 or Q**H*C or 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, dimension (MAX(1,LWORK))
          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
[in]LWORK
          LWORK is INTEGER
          The dimension of the array WORK.
          If SIDE = 'L', LWORK >= max(1,N);
          if SIDE = 'R', LWORK >= max(1,M).
          For good performance, LWORK should generally be larger.

          If LWORK = -1, then a workspace query is assumed; the routine
          only calculates the optimal size of the WORK array, returns
          this value as the first entry of the WORK array, and no error
          message related to LWORK is issued by XERBLA.
[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 cunmlq.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, LDA, LDC, LWORK, M, N
176* ..
177* .. Array Arguments ..
178 COMPLEX A( LDA, * ), C( LDC, * ), TAU( * ),
179 $ WORK( * )
180* ..
181*
182* =====================================================================
183*
184* .. Parameters ..
185 INTEGER NBMAX, LDT, TSIZE
186 parameter( nbmax = 64, ldt = nbmax+1,
187 $ tsize = ldt*nbmax )
188* ..
189* .. Local Scalars ..
190 LOGICAL LEFT, LQUERY, NOTRAN
191 CHARACTER TRANST
192 INTEGER I, I1, I2, I3, IB, IC, IINFO, IWT, JC, LDWORK,
193 $ LWKOPT, MI, NB, NBMIN, NI, NQ, NW
194* ..
195* .. External Functions ..
196 LOGICAL LSAME
197 INTEGER ILAENV
198 REAL SROUNDUP_LWORK
199 EXTERNAL lsame, ilaenv, sroundup_lwork
200* ..
201* .. External Subroutines ..
202 EXTERNAL clarfb, clarft, cunml2, xerbla
203* ..
204* .. Intrinsic Functions ..
205 INTRINSIC max, min
206* ..
207* .. Executable Statements ..
208*
209* Test the input arguments
210*
211 info = 0
212 left = lsame( side, 'L' )
213 notran = lsame( trans, 'N' )
214 lquery = ( lwork.EQ.-1 )
215*
216* NQ is the order of Q and NW is the minimum dimension of WORK
217*
218 IF( left ) THEN
219 nq = m
220 nw = max( 1, n )
221 ELSE
222 nq = n
223 nw = max( 1, m )
224 END IF
225 IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
226 info = -1
227 ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'C' ) ) THEN
228 info = -2
229 ELSE IF( m.LT.0 ) THEN
230 info = -3
231 ELSE IF( n.LT.0 ) THEN
232 info = -4
233 ELSE IF( k.LT.0 .OR. k.GT.nq ) THEN
234 info = -5
235 ELSE IF( lda.LT.max( 1, k ) ) THEN
236 info = -7
237 ELSE IF( ldc.LT.max( 1, m ) ) THEN
238 info = -10
239 ELSE IF( lwork.LT.nw .AND. .NOT.lquery ) THEN
240 info = -12
241 END IF
242*
243 IF( info.EQ.0 ) THEN
244*
245* Compute the workspace requirements
246*
247 IF( m.EQ.0 .OR. n.EQ.0 .OR. k.EQ.0 ) THEN
248 lwkopt = 1
249 ELSE
250 nb = min( nbmax, ilaenv( 1, 'CUNMLQ', side // trans, m, n,
251 $ k, -1 ) )
252 lwkopt = nw*nb + tsize
253 END IF
254 work( 1 ) = sroundup_lwork(lwkopt)
255 END IF
256*
257 IF( info.NE.0 ) THEN
258 CALL xerbla( 'CUNMLQ', -info )
259 RETURN
260 ELSE IF( lquery ) THEN
261 RETURN
262 END IF
263*
264* Quick return if possible
265*
266 IF( m.EQ.0 .OR. n.EQ.0 .OR. k.EQ.0 ) THEN
267 RETURN
268 END IF
269*
270* Determine the block size
271*
272 nbmin = 2
273 ldwork = nw
274 IF( nb.GT.1 .AND. nb.LT.k ) THEN
275 IF( lwork.LT.lwkopt ) THEN
276 nb = (lwork-tsize) / ldwork
277 nbmin = max( 2, ilaenv( 2, 'CUNMLQ', side // trans, m, n, k,
278 $ -1 ) )
279 END IF
280 END IF
281*
282 IF( nb.LT.nbmin .OR. nb.GE.k ) THEN
283*
284* Use unblocked code
285*
286 CALL cunml2( side, trans, m, n, k, a, lda, tau, c, ldc, work,
287 $ iinfo )
288 ELSE
289*
290* Use blocked code
291*
292 iwt = 1 + nw*nb
293 IF( ( left .AND. notran ) .OR.
294 $ ( .NOT.left .AND. .NOT.notran ) ) THEN
295 i1 = 1
296 i2 = k
297 i3 = nb
298 ELSE
299 i1 = ( ( k-1 ) / nb )*nb + 1
300 i2 = 1
301 i3 = -nb
302 END IF
303*
304 IF( left ) THEN
305 ni = n
306 jc = 1
307 ELSE
308 mi = m
309 ic = 1
310 END IF
311*
312 IF( notran ) THEN
313 transt = 'C'
314 ELSE
315 transt = 'N'
316 END IF
317*
318 DO 10 i = i1, i2, i3
319 ib = min( nb, k-i+1 )
320*
321* Form the triangular factor of the block reflector
322* H = H(i) H(i+1) . . . H(i+ib-1)
323*
324 CALL clarft( 'Forward', 'Rowwise', nq-i+1, ib, a( i, i ),
325 $ lda, tau( i ), work( iwt ), ldt )
326 IF( left ) THEN
327*
328* H or H**H is applied to C(i:m,1:n)
329*
330 mi = m - i + 1
331 ic = i
332 ELSE
333*
334* H or H**H is applied to C(1:m,i:n)
335*
336 ni = n - i + 1
337 jc = i
338 END IF
339*
340* Apply H or H**H
341*
342 CALL clarfb( side, transt, 'Forward', 'Rowwise', mi, ni, ib,
343 $ a( i, i ), lda, work( iwt ), ldt,
344 $ c( ic, jc ), ldc, work, ldwork )
345 10 CONTINUE
346 END IF
347 work( 1 ) = sroundup_lwork(lwkopt)
348 RETURN
349*
350* End of CUNMLQ
351*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:162
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
subroutine clarft(direct, storev, n, k, v, ldv, tau, t, ldt)
CLARFT forms the triangular factor T of a block reflector H = I - vtvH
Definition clarft.f:163
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
real function sroundup_lwork(lwork)
SROUNDUP_LWORK
subroutine cunml2(side, trans, m, n, k, a, lda, tau, c, ldc, work, info)
CUNML2 multiplies a general matrix by the unitary matrix from a LQ factorization determined by cgelqf...
Definition cunml2.f:159
Here is the call graph for this function:
Here is the caller graph for this function: