LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine zunmqr ( character  SIDE,
character  TRANS,
integer  M,
integer  N,
integer  K,
complex*16, dimension( lda, * )  A,
integer  LDA,
complex*16, dimension( * )  TAU,
complex*16, dimension( ldc, * )  C,
integer  LDC,
complex*16, dimension( * )  WORK,
integer  LWORK,
integer  INFO 
)

ZUNMQR

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

Purpose:
 ZUNMQR 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(1) H(2) . . . H(k)

 as returned by ZGEQRF. 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*16 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
          ZGEQRF in the first 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*16 array, dimension (K)
          TAU(i) must contain the scalar factor of the elementary
          reflector H(i), as returned by ZGEQRF.
[in,out]C
          C is COMPLEX*16 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*16 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 169 of file zunmqr.f.

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