LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine cunmql ( 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 
)

CUNMQL

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

Purpose:
 CUNMQL 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(2) H(1)

 as returned by CGEQLF. 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':  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,K)
          The i-th column must contain the vector which defines the
          elementary reflector H(i), for i = 1,2,...,k, as returned by
          CGEQLF in the last k columns of its array argument A.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.
          If SIDE = 'L', LDA >= max(1,M);
          if SIDE = 'R', LDA >= max(1,N).
[in]TAU
          TAU is COMPLEX array, dimension (K)
          TAU(i) must contain the scalar factor of the elementary
          reflector H(i), as returned by CGEQLF.
[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 cunmql.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  INTEGER i, i1, i2, i3, ib, iinfo, iwt, ldwork, lwkopt,
195  $ mi, nb, nbmin, ni, nq, nw
196 * ..
197 * .. External Functions ..
198  LOGICAL lsame
199  INTEGER ilaenv
200  EXTERNAL lsame, ilaenv
201 * ..
202 * .. External Subroutines ..
203  EXTERNAL clarfb, clarft, cunm2l, xerbla
204 * ..
205 * .. Intrinsic Functions ..
206  INTRINSIC max, min
207 * ..
208 * .. Executable Statements ..
209 *
210 * Test the input arguments
211 *
212  info = 0
213  left = lsame( side, 'L' )
214  notran = lsame( trans, 'N' )
215  lquery = ( lwork.EQ.-1 )
216 *
217 * NQ is the order of Q and NW is the minimum dimension of WORK
218 *
219  IF( left ) THEN
220  nq = m
221  nw = max( 1, n )
222  ELSE
223  nq = n
224  nw = max( 1, m )
225  END IF
226  IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
227  info = -1
228  ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'C' ) ) THEN
229  info = -2
230  ELSE IF( m.LT.0 ) THEN
231  info = -3
232  ELSE IF( n.LT.0 ) THEN
233  info = -4
234  ELSE IF( k.LT.0 .OR. k.GT.nq ) THEN
235  info = -5
236  ELSE IF( lda.LT.max( 1, nq ) ) THEN
237  info = -7
238  ELSE IF( ldc.LT.max( 1, m ) ) THEN
239  info = -10
240  ELSE IF( lwork.LT.nw .AND. .NOT.lquery ) THEN
241  info = -12
242  END IF
243 *
244  IF( info.EQ.0 ) THEN
245 *
246 * Compute the workspace requirements
247 *
248  IF( m.EQ.0 .OR. n.EQ.0 ) THEN
249  lwkopt = 1
250  ELSE
251  nb = min( nbmax, ilaenv( 1, 'CUNMQL', side // trans, m, n,
252  $ k, -1 ) )
253  lwkopt = nw*nb + tsize
254  END IF
255  work( 1 ) = lwkopt
256  END IF
257 *
258  IF( info.NE.0 ) THEN
259  CALL xerbla( 'CUNMQL', -info )
260  RETURN
261  ELSE IF( lquery ) THEN
262  RETURN
263  END IF
264 *
265 * Quick return if possible
266 *
267  IF( m.EQ.0 .OR. n.EQ.0 ) THEN
268  RETURN
269  END IF
270 *
271 * Determine the block size
272 *
273  nbmin = 2
274  ldwork = nw
275  IF( nb.GT.1 .AND. nb.LT.k ) THEN
276  IF( lwork.LT.(nw*nb+tsize) ) THEN
277  nb = (lwork-tsize) / ldwork
278  nbmin = max( 2, ilaenv( 2, 'CUNMQL', side // trans, m, n, k,
279  $ -1 ) )
280  END IF
281  END IF
282 *
283  IF( nb.LT.nbmin .OR. nb.GE.k ) THEN
284 *
285 * Use unblocked code
286 *
287  CALL cunm2l( side, trans, m, n, k, a, lda, tau, c, ldc, work,
288  $ iinfo )
289  ELSE
290 *
291 * Use blocked code
292 *
293  iwt = 1 + nw*nb
294  IF( ( left .AND. notran ) .OR.
295  $ ( .NOT.left .AND. .NOT.notran ) ) THEN
296  i1 = 1
297  i2 = k
298  i3 = nb
299  ELSE
300  i1 = ( ( k-1 ) / nb )*nb + 1
301  i2 = 1
302  i3 = -nb
303  END IF
304 *
305  IF( left ) THEN
306  ni = n
307  ELSE
308  mi = m
309  END IF
310 *
311  DO 10 i = i1, i2, i3
312  ib = min( nb, k-i+1 )
313 *
314 * Form the triangular factor of the block reflector
315 * H = H(i+ib-1) . . . H(i+1) H(i)
316 *
317  CALL clarft( 'Backward', 'Columnwise', nq-k+i+ib-1, ib,
318  $ a( 1, i ), lda, tau( i ), work( iwt ), ldt )
319  IF( left ) THEN
320 *
321 * H or H**H is applied to C(1:m-k+i+ib-1,1:n)
322 *
323  mi = m - k + i + ib - 1
324  ELSE
325 *
326 * H or H**H is applied to C(1:m,1:n-k+i+ib-1)
327 *
328  ni = n - k + i + ib - 1
329  END IF
330 *
331 * Apply H or H**H
332 *
333  CALL clarfb( side, trans, 'Backward', 'Columnwise', mi, ni,
334  $ ib, a( 1, i ), lda, work( iwt ), ldt, c, ldc,
335  $ work, ldwork )
336  10 CONTINUE
337  END IF
338  work( 1 ) = lwkopt
339  RETURN
340 *
341 * End of CUNMQL
342 *
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 cunm2l(SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, INFO)
CUNM2L multiplies a general matrix by the unitary matrix from a QL factorization determined by cgeqlf...
Definition: cunm2l.f:161
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
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: