LAPACK 3.12.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 REAL SROUNDUP_LWORK
217 EXTERNAL lsame, ilaenv, sroundup_lwork
218* ..
219* .. External Subroutines ..
220 EXTERNAL clarzb, clarzt, cunmr3, xerbla
221* ..
222* .. Intrinsic Functions ..
223 INTRINSIC max, min
224* ..
225* .. Executable Statements ..
226*
227* Test the input arguments
228*
229 info = 0
230 left = lsame( side, 'L' )
231 notran = lsame( trans, 'N' )
232 lquery = ( lwork.EQ.-1 )
233*
234* NQ is the order of Q and NW is the minimum dimension of WORK
235*
236 IF( left ) THEN
237 nq = m
238 nw = max( 1, n )
239 ELSE
240 nq = n
241 nw = max( 1, m )
242 END IF
243 IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
244 info = -1
245 ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'C' ) ) THEN
246 info = -2
247 ELSE IF( m.LT.0 ) THEN
248 info = -3
249 ELSE IF( n.LT.0 ) THEN
250 info = -4
251 ELSE IF( k.LT.0 .OR. k.GT.nq ) THEN
252 info = -5
253 ELSE IF( l.LT.0 .OR. ( left .AND. ( l.GT.m ) ) .OR.
254 $ ( .NOT.left .AND. ( l.GT.n ) ) ) THEN
255 info = -6
256 ELSE IF( lda.LT.max( 1, k ) ) THEN
257 info = -8
258 ELSE IF( ldc.LT.max( 1, m ) ) THEN
259 info = -11
260 ELSE IF( lwork.LT.nw .AND. .NOT.lquery ) THEN
261 info = -13
262 END IF
263*
264 IF( info.EQ.0 ) THEN
265*
266* Compute the workspace requirements
267*
268 IF( m.EQ.0 .OR. n.EQ.0 ) THEN
269 lwkopt = 1
270 ELSE
271 nb = min( nbmax, ilaenv( 1, 'CUNMRQ', side // trans, m, n,
272 $ k, -1 ) )
273 lwkopt = nw*nb + tsize
274 END IF
275 work( 1 ) = sroundup_lwork(lwkopt)
276 END IF
277*
278 IF( info.NE.0 ) THEN
279 CALL xerbla( 'CUNMRZ', -info )
280 RETURN
281 ELSE IF( lquery ) THEN
282 RETURN
283 END IF
284*
285* Quick return if possible
286*
287 IF( m.EQ.0 .OR. n.EQ.0 ) THEN
288 RETURN
289 END IF
290*
291* Determine the block size.
292*
293 nb = min( nbmax, ilaenv( 1, 'CUNMRQ', side // trans, m, n, k,
294 $ -1 ) )
295 nbmin = 2
296 ldwork = nw
297 IF( nb.GT.1 .AND. nb.LT.k ) THEN
298 IF( lwork.LT.lwkopt ) THEN
299 nb = (lwork-tsize) / ldwork
300 nbmin = max( 2, ilaenv( 2, 'CUNMRQ', side // trans, m, n, k,
301 $ -1 ) )
302 END IF
303 END IF
304*
305 IF( nb.LT.nbmin .OR. nb.GE.k ) THEN
306*
307* Use unblocked code
308*
309 CALL cunmr3( side, trans, m, n, k, l, a, lda, tau, c, ldc,
310 $ work, iinfo )
311 ELSE
312*
313* Use blocked code
314*
315 iwt = 1 + nw*nb
316 IF( ( left .AND. .NOT.notran ) .OR.
317 $ ( .NOT.left .AND. notran ) ) THEN
318 i1 = 1
319 i2 = k
320 i3 = nb
321 ELSE
322 i1 = ( ( k-1 ) / nb )*nb + 1
323 i2 = 1
324 i3 = -nb
325 END IF
326*
327 IF( left ) THEN
328 ni = n
329 jc = 1
330 ja = m - l + 1
331 ELSE
332 mi = m
333 ic = 1
334 ja = n - l + 1
335 END IF
336*
337 IF( notran ) THEN
338 transt = 'C'
339 ELSE
340 transt = 'N'
341 END IF
342*
343 DO 10 i = i1, i2, i3
344 ib = min( nb, k-i+1 )
345*
346* Form the triangular factor of the block reflector
347* H = H(i+ib-1) . . . H(i+1) H(i)
348*
349 CALL clarzt( 'Backward', 'Rowwise', l, ib, a( i, ja ), lda,
350 $ tau( i ), work( iwt ), ldt )
351*
352 IF( left ) THEN
353*
354* H or H**H is applied to C(i:m,1:n)
355*
356 mi = m - i + 1
357 ic = i
358 ELSE
359*
360* H or H**H is applied to C(1:m,i:n)
361*
362 ni = n - i + 1
363 jc = i
364 END IF
365*
366* Apply H or H**H
367*
368 CALL clarzb( side, transt, 'Backward', 'Rowwise', mi, ni,
369 $ ib, l, a( i, ja ), lda, work( iwt ), ldt,
370 $ c( ic, jc ), ldc, work, ldwork )
371 10 CONTINUE
372*
373 END IF
374*
375 work( 1 ) = sroundup_lwork(lwkopt)
376*
377 RETURN
378*
379* End of CUNMRZ
380*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:162
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
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
real function sroundup_lwork(lwork)
SROUNDUP_LWORK
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: