LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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.
Date
November 2015

Definition at line 170 of file cunmlq.f.

170 *
171 * -- LAPACK computational routine (version 3.6.0) --
172 * -- LAPACK is a software package provided by Univ. of Tennessee, --
173 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
174 * November 2015
175 *
176 * .. Scalar Arguments ..
177  CHARACTER side, trans
178  INTEGER info, k, lda, ldc, lwork, m, n
179 * ..
180 * .. Array Arguments ..
181  COMPLEX a( lda, * ), c( ldc, * ), tau( * ),
182  $ work( * )
183 * ..
184 *
185 * =====================================================================
186 *
187 * .. Parameters ..
188  INTEGER nbmax, ldt, tsize
189  parameter ( nbmax = 64, ldt = nbmax+1,
190  $ tsize = ldt*nbmax )
191 * ..
192 * .. Local Scalars ..
193  LOGICAL left, lquery, notran
194  CHARACTER transt
195  INTEGER i, i1, i2, i3, ib, ic, iinfo, iwt, jc, ldwork,
196  $ lwkopt, mi, nb, nbmin, ni, nq, nw
197 * ..
198 * .. External Functions ..
199  LOGICAL lsame
200  INTEGER ilaenv
201  EXTERNAL lsame, ilaenv
202 * ..
203 * .. External Subroutines ..
204  EXTERNAL clarfb, clarft, cunml2, xerbla
205 * ..
206 * .. Intrinsic Functions ..
207  INTRINSIC max, min
208 * ..
209 * .. Executable Statements ..
210 *
211 * Test the input arguments
212 *
213  info = 0
214  left = lsame( side, 'L' )
215  notran = lsame( trans, 'N' )
216  lquery = ( lwork.EQ.-1 )
217 *
218 * NQ is the order of Q and NW is the minimum dimension of WORK
219 *
220  IF( left ) THEN
221  nq = m
222  nw = n
223  ELSE
224  nq = n
225  nw = m
226  END IF
227  IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
228  info = -1
229  ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'C' ) ) THEN
230  info = -2
231  ELSE IF( m.LT.0 ) THEN
232  info = -3
233  ELSE IF( n.LT.0 ) THEN
234  info = -4
235  ELSE IF( k.LT.0 .OR. k.GT.nq ) THEN
236  info = -5
237  ELSE IF( lda.LT.max( 1, k ) ) THEN
238  info = -7
239  ELSE IF( ldc.LT.max( 1, m ) ) THEN
240  info = -10
241  ELSE IF( lwork.LT.max( 1, nw ) .AND. .NOT.lquery ) THEN
242  info = -12
243  END IF
244 *
245  IF( info.EQ.0 ) THEN
246 *
247 * Compute the workspace requirements
248 *
249  IF( m.EQ.0 .OR. n.EQ.0 .OR. k.EQ.0 ) THEN
250  lwkopt = 1
251  ELSE
252  nb = min( nbmax, ilaenv( 1, 'CUNMLQ', side // trans, m, n,
253  $ k, -1 ) )
254  lwkopt = max( 1, nw )*nb + tsize
255  END IF
256  work( 1 ) = lwkopt
257  END IF
258 *
259  IF( info.NE.0 ) THEN
260  CALL xerbla( 'CUNMLQ', -info )
261  RETURN
262  ELSE IF( lquery ) THEN
263  RETURN
264  END IF
265 *
266 * Quick return if possible
267 *
268  IF( m.EQ.0 .OR. n.EQ.0 .OR. k.EQ.0 ) THEN
269  RETURN
270  END IF
271 *
272 * Determine the block size
273 *
274  nbmin = 2
275  ldwork = nw
276  IF( nb.GT.1 .AND. nb.LT.k ) THEN
277  IF( lwork.LT.nw*nb+tsize ) THEN
278  nb = (lwork-tsize) / ldwork
279  nbmin = max( 2, ilaenv( 2, 'CUNMLQ', side // trans, m, n, k,
280  $ -1 ) )
281  END IF
282  END IF
283 *
284  IF( nb.LT.nbmin .OR. nb.GE.k ) THEN
285 *
286 * Use unblocked code
287 *
288  CALL cunml2( side, trans, m, n, k, a, lda, tau, c, ldc, work,
289  $ iinfo )
290  ELSE
291 *
292 * Use blocked code
293 *
294  iwt = 1 + nw*nb
295  IF( ( left .AND. notran ) .OR.
296  $ ( .NOT.left .AND. .NOT.notran ) ) THEN
297  i1 = 1
298  i2 = k
299  i3 = nb
300  ELSE
301  i1 = ( ( k-1 ) / nb )*nb + 1
302  i2 = 1
303  i3 = -nb
304  END IF
305 *
306  IF( left ) THEN
307  ni = n
308  jc = 1
309  ELSE
310  mi = m
311  ic = 1
312  END IF
313 *
314  IF( notran ) THEN
315  transt = 'C'
316  ELSE
317  transt = 'N'
318  END IF
319 *
320  DO 10 i = i1, i2, i3
321  ib = min( nb, k-i+1 )
322 *
323 * Form the triangular factor of the block reflector
324 * H = H(i) H(i+1) . . . H(i+ib-1)
325 *
326  CALL clarft( 'Forward', 'Rowwise', nq-i+1, ib, a( i, i ),
327  $ lda, tau( i ), work( iwt ), ldt )
328  IF( left ) THEN
329 *
330 * H or H**H is applied to C(i:m,1:n)
331 *
332  mi = m - i + 1
333  ic = i
334  ELSE
335 *
336 * H or H**H is applied to C(1:m,i:n)
337 *
338  ni = n - i + 1
339  jc = i
340  END IF
341 *
342 * Apply H or H**H
343 *
344  CALL clarfb( side, transt, 'Forward', 'Rowwise', mi, ni, ib,
345  $ a( i, i ), lda, work( iwt ), ldt,
346  $ c( ic, jc ), ldc, work, ldwork )
347  10 CONTINUE
348  END IF
349  work( 1 ) = lwkopt
350  RETURN
351 *
352 * End of CUNMLQ
353 *
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:165
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
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:161
integer function ilaenv(ISPEC, NAME, OPTS, N1, N2, N3, N4)
Definition: tstiee.f:83
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:55

Here is the call graph for this function:

Here is the caller graph for this function: