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

◆ cunmrz()

subroutine cunmrz ( character  SIDE,
character  TRANS,
integer  M,
integer  N,
integer  K,
integer  L,
complex, dimension( lda, * )  A,
integer  LDA,
complex, dimension( * )  TAU,
complex, dimension( ldc, * )  C,
integer  LDC,
complex, dimension( * )  WORK,
integer  LWORK,
integer  INFO 
)

CUNMRZ

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

Purpose:
 CUNMRZ 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 CTZRZF. 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]L
          L is INTEGER
          The number of columns of the matrix A containing
          the meaningful part of the Householder reflectors.
          If SIDE = 'L', M >= L >= 0, if SIDE = 'R', N >= L >= 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
          CTZRZF in the last k rows of its array argument A.
          A is modified by the routine but restored on exit.
[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 CTZRZF.
[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.
Contributors:
A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
Further Details:
 

Definition at line 185 of file cunmrz.f.

187*
188* -- LAPACK computational routine --
189* -- LAPACK is a software package provided by Univ. of Tennessee, --
190* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
191*
192* .. Scalar Arguments ..
193 CHARACTER SIDE, TRANS
194 INTEGER INFO, K, L, LDA, LDC, LWORK, M, N
195* ..
196* .. Array Arguments ..
197 COMPLEX A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
198* ..
199*
200* =====================================================================
201*
202* .. Parameters ..
203 INTEGER NBMAX, LDT, TSIZE
204 parameter( nbmax = 64, ldt = nbmax+1,
205 $ tsize = ldt*nbmax )
206* ..
207* .. Local Scalars ..
208 LOGICAL LEFT, LQUERY, NOTRAN
209 CHARACTER TRANST
210 INTEGER I, I1, I2, I3, IB, IC, IINFO, IWT, JA, JC,
211 $ LDWORK, LWKOPT, MI, NB, NBMIN, NI, NQ, NW
212* ..
213* .. External Functions ..
214 LOGICAL LSAME
215 INTEGER ILAENV
216 EXTERNAL lsame, ilaenv
217* ..
218* .. External Subroutines ..
219 EXTERNAL clarzb, clarzt, cunmr3, xerbla
220* ..
221* .. Intrinsic Functions ..
222 INTRINSIC max, min
223* ..
224* .. Executable Statements ..
225*
226* Test the input arguments
227*
228 info = 0
229 left = lsame( side, 'L' )
230 notran = lsame( trans, 'N' )
231 lquery = ( lwork.EQ.-1 )
232*
233* NQ is the order of Q and NW is the minimum dimension of WORK
234*
235 IF( left ) THEN
236 nq = m
237 nw = max( 1, n )
238 ELSE
239 nq = n
240 nw = max( 1, m )
241 END IF
242 IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
243 info = -1
244 ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'C' ) ) THEN
245 info = -2
246 ELSE IF( m.LT.0 ) THEN
247 info = -3
248 ELSE IF( n.LT.0 ) THEN
249 info = -4
250 ELSE IF( k.LT.0 .OR. k.GT.nq ) THEN
251 info = -5
252 ELSE IF( l.LT.0 .OR. ( left .AND. ( l.GT.m ) ) .OR.
253 $ ( .NOT.left .AND. ( l.GT.n ) ) ) THEN
254 info = -6
255 ELSE IF( lda.LT.max( 1, k ) ) THEN
256 info = -8
257 ELSE IF( ldc.LT.max( 1, m ) ) THEN
258 info = -11
259 ELSE IF( lwork.LT.nw .AND. .NOT.lquery ) THEN
260 info = -13
261 END IF
262*
263 IF( info.EQ.0 ) THEN
264*
265* Compute the workspace requirements
266*
267 IF( m.EQ.0 .OR. n.EQ.0 ) THEN
268 lwkopt = 1
269 ELSE
270 nb = min( nbmax, ilaenv( 1, 'CUNMRQ', side // trans, m, n,
271 $ k, -1 ) )
272 lwkopt = nw*nb + tsize
273 END IF
274 work( 1 ) = lwkopt
275 END IF
276*
277 IF( info.NE.0 ) THEN
278 CALL xerbla( 'CUNMRZ', -info )
279 RETURN
280 ELSE IF( lquery ) THEN
281 RETURN
282 END IF
283*
284* Quick return if possible
285*
286 IF( m.EQ.0 .OR. n.EQ.0 ) THEN
287 RETURN
288 END IF
289*
290* Determine the block size.
291*
292 nb = min( nbmax, ilaenv( 1, 'CUNMRQ', side // trans, m, n, k,
293 $ -1 ) )
294 nbmin = 2
295 ldwork = nw
296 IF( nb.GT.1 .AND. nb.LT.k ) THEN
297 IF( lwork.LT.lwkopt ) THEN
298 nb = (lwork-tsize) / ldwork
299 nbmin = max( 2, ilaenv( 2, 'CUNMRQ', side // trans, m, n, k,
300 $ -1 ) )
301 END IF
302 END IF
303*
304 IF( nb.LT.nbmin .OR. nb.GE.k ) THEN
305*
306* Use unblocked code
307*
308 CALL cunmr3( side, trans, m, n, k, l, a, lda, tau, c, ldc,
309 $ work, iinfo )
310 ELSE
311*
312* Use blocked code
313*
314 iwt = 1 + nw*nb
315 IF( ( left .AND. .NOT.notran ) .OR.
316 $ ( .NOT.left .AND. notran ) ) THEN
317 i1 = 1
318 i2 = k
319 i3 = nb
320 ELSE
321 i1 = ( ( k-1 ) / nb )*nb + 1
322 i2 = 1
323 i3 = -nb
324 END IF
325*
326 IF( left ) THEN
327 ni = n
328 jc = 1
329 ja = m - l + 1
330 ELSE
331 mi = m
332 ic = 1
333 ja = n - l + 1
334 END IF
335*
336 IF( notran ) THEN
337 transt = 'C'
338 ELSE
339 transt = 'N'
340 END IF
341*
342 DO 10 i = i1, i2, i3
343 ib = min( nb, k-i+1 )
344*
345* Form the triangular factor of the block reflector
346* H = H(i+ib-1) . . . H(i+1) H(i)
347*
348 CALL clarzt( 'Backward', 'Rowwise', l, ib, a( i, ja ), lda,
349 $ tau( i ), work( iwt ), ldt )
350*
351 IF( left ) THEN
352*
353* H or H**H is applied to C(i:m,1:n)
354*
355 mi = m - i + 1
356 ic = i
357 ELSE
358*
359* H or H**H is applied to C(1:m,i:n)
360*
361 ni = n - i + 1
362 jc = i
363 END IF
364*
365* Apply H or H**H
366*
367 CALL clarzb( side, transt, 'Backward', 'Rowwise', mi, ni,
368 $ ib, l, a( i, ja ), lda, work( iwt ), ldt,
369 $ c( ic, jc ), ldc, work, ldwork )
370 10 CONTINUE
371*
372 END IF
373*
374 work( 1 ) = lwkopt
375*
376 RETURN
377*
378* End of CUNMRZ
379*
integer function ilaenv(ISPEC, NAME, OPTS, N1, N2, N3, N4)
ILAENV
Definition: ilaenv.f:162
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:60
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:53
subroutine clarzb(SIDE, TRANS, DIRECT, STOREV, M, N, K, L, V, LDV, T, LDT, C, LDC, WORK, LDWORK)
CLARZB applies a block reflector or its conjugate-transpose to a general matrix.
Definition: clarzb.f:183
subroutine clarzt(DIRECT, STOREV, N, K, V, LDV, TAU, T, LDT)
CLARZT forms the triangular factor T of a block reflector H = I - vtvH.
Definition: clarzt.f:185
subroutine cunmr3(SIDE, TRANS, M, N, K, L, A, LDA, TAU, C, LDC, WORK, INFO)
CUNMR3 multiplies a general matrix by the unitary matrix from a RZ factorization determined by ctzrzf...
Definition: cunmr3.f:178
Here is the call graph for this function:
Here is the caller graph for this function: