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

◆ dormrz()

subroutine dormrz ( character  side,
character  trans,
integer  m,
integer  n,
integer  k,
integer  l,
double precision, dimension( lda, * )  a,
integer  lda,
double precision, dimension( * )  tau,
double precision, dimension( ldc, * )  c,
integer  ldc,
double precision, dimension( * )  work,
integer  lwork,
integer  info 
)

DORMRZ

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

Purpose:
 DORMRZ overwrites the general real M-by-N matrix C with

                 SIDE = 'L'     SIDE = 'R'
 TRANS = 'N':      Q * C          C * Q
 TRANS = 'T':      Q**T * C       C * Q**T

 where Q is a real orthogonal matrix defined as the product of k
 elementary reflectors

       Q = H(1) H(2) . . . H(k)

 as returned by DTZRZF. 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**T from the Left;
          = 'R': apply Q or Q**T from the Right.
[in]TRANS
          TRANS is CHARACTER*1
          = 'N':  No transpose, apply Q;
          = 'T':  Transpose, apply Q**T.
[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 DOUBLE PRECISION 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
          DTZRZF 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 DOUBLE PRECISION array, dimension (K)
          TAU(i) must contain the scalar factor of the elementary
          reflector H(i), as returned by DTZRZF.
[in,out]C
          C is DOUBLE PRECISION 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 DOUBLE PRECISION 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 dormrz.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 DOUBLE PRECISION 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 dlarzb, dlarzt, dormr3, 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, 'T' ) ) 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, 'DORMRQ', 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( 'DORMRZ', -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 work( 1 ) = 1
288 RETURN
289 END IF
290*
291 nbmin = 2
292 ldwork = nw
293 IF( nb.GT.1 .AND. nb.LT.k ) THEN
294 IF( lwork.LT.lwkopt ) THEN
295 nb = (lwork-tsize) / ldwork
296 nbmin = max( 2, ilaenv( 2, 'DORMRQ', side // trans, m, n, k,
297 $ -1 ) )
298 END IF
299 END IF
300*
301 IF( nb.LT.nbmin .OR. nb.GE.k ) THEN
302*
303* Use unblocked code
304*
305 CALL dormr3( side, trans, m, n, k, l, a, lda, tau, c, ldc,
306 $ work, iinfo )
307 ELSE
308*
309* Use blocked code
310*
311 iwt = 1 + nw*nb
312 IF( ( left .AND. .NOT.notran ) .OR.
313 $ ( .NOT.left .AND. notran ) ) THEN
314 i1 = 1
315 i2 = k
316 i3 = nb
317 ELSE
318 i1 = ( ( k-1 ) / nb )*nb + 1
319 i2 = 1
320 i3 = -nb
321 END IF
322*
323 IF( left ) THEN
324 ni = n
325 jc = 1
326 ja = m - l + 1
327 ELSE
328 mi = m
329 ic = 1
330 ja = n - l + 1
331 END IF
332*
333 IF( notran ) THEN
334 transt = 'T'
335 ELSE
336 transt = 'N'
337 END IF
338*
339 DO 10 i = i1, i2, i3
340 ib = min( nb, k-i+1 )
341*
342* Form the triangular factor of the block reflector
343* H = H(i+ib-1) . . . H(i+1) H(i)
344*
345 CALL dlarzt( 'Backward', 'Rowwise', l, ib, a( i, ja ), lda,
346 $ tau( i ), work( iwt ), ldt )
347*
348 IF( left ) THEN
349*
350* H or H**T is applied to C(i:m,1:n)
351*
352 mi = m - i + 1
353 ic = i
354 ELSE
355*
356* H or H**T is applied to C(1:m,i:n)
357*
358 ni = n - i + 1
359 jc = i
360 END IF
361*
362* Apply H or H**T
363*
364 CALL dlarzb( side, transt, 'Backward', 'Rowwise', mi, ni,
365 $ ib, l, a( i, ja ), lda, work( iwt ), ldt,
366 $ c( ic, jc ), ldc, work, ldwork )
367 10 CONTINUE
368*
369 END IF
370*
371 work( 1 ) = lwkopt
372*
373 RETURN
374*
375* End of DORMRZ
376*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:162
subroutine dlarzb(side, trans, direct, storev, m, n, k, l, v, ldv, t, ldt, c, ldc, work, ldwork)
DLARZB applies a block reflector or its transpose to a general matrix.
Definition dlarzb.f:183
subroutine dlarzt(direct, storev, n, k, v, ldv, tau, t, ldt)
DLARZT forms the triangular factor T of a block reflector H = I - vtvH.
Definition dlarzt.f:185
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine dormr3(side, trans, m, n, k, l, a, lda, tau, c, ldc, work, info)
DORMR3 multiplies a general matrix by the orthogonal matrix from a RZ factorization determined by stz...
Definition dormr3.f:178
Here is the call graph for this function:
Here is the caller graph for this function: