LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
dormrz.f
Go to the documentation of this file.
1 *> \brief \b DORMRZ
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download DORMRZ + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dormrz.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dormrz.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dormrz.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE DORMRZ( SIDE, TRANS, M, N, K, L, A, LDA, TAU, C, LDC,
22 * WORK, LWORK, INFO )
23 *
24 * .. Scalar Arguments ..
25 * CHARACTER SIDE, TRANS
26 * INTEGER INFO, K, L, LDA, LDC, LWORK, M, N
27 * ..
28 * .. Array Arguments ..
29 * DOUBLE PRECISION A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
30 * ..
31 *
32 *
33 *> \par Purpose:
34 * =============
35 *>
36 *> \verbatim
37 *>
38 *> DORMRZ overwrites the general real M-by-N matrix C with
39 *>
40 *> SIDE = 'L' SIDE = 'R'
41 *> TRANS = 'N': Q * C C * Q
42 *> TRANS = 'T': Q**T * C C * Q**T
43 *>
44 *> where Q is a real orthogonal matrix defined as the product of k
45 *> elementary reflectors
46 *>
47 *> Q = H(1) H(2) . . . H(k)
48 *>
49 *> as returned by DTZRZF. Q is of order M if SIDE = 'L' and of order N
50 *> if SIDE = 'R'.
51 *> \endverbatim
52 *
53 * Arguments:
54 * ==========
55 *
56 *> \param[in] SIDE
57 *> \verbatim
58 *> SIDE is CHARACTER*1
59 *> = 'L': apply Q or Q**T from the Left;
60 *> = 'R': apply Q or Q**T from the Right.
61 *> \endverbatim
62 *>
63 *> \param[in] TRANS
64 *> \verbatim
65 *> TRANS is CHARACTER*1
66 *> = 'N': No transpose, apply Q;
67 *> = 'T': Transpose, apply Q**T.
68 *> \endverbatim
69 *>
70 *> \param[in] M
71 *> \verbatim
72 *> M is INTEGER
73 *> The number of rows of the matrix C. M >= 0.
74 *> \endverbatim
75 *>
76 *> \param[in] N
77 *> \verbatim
78 *> N is INTEGER
79 *> The number of columns of the matrix C. N >= 0.
80 *> \endverbatim
81 *>
82 *> \param[in] K
83 *> \verbatim
84 *> K is INTEGER
85 *> The number of elementary reflectors whose product defines
86 *> the matrix Q.
87 *> If SIDE = 'L', M >= K >= 0;
88 *> if SIDE = 'R', N >= K >= 0.
89 *> \endverbatim
90 *>
91 *> \param[in] L
92 *> \verbatim
93 *> L is INTEGER
94 *> The number of columns of the matrix A containing
95 *> the meaningful part of the Householder reflectors.
96 *> If SIDE = 'L', M >= L >= 0, if SIDE = 'R', N >= L >= 0.
97 *> \endverbatim
98 *>
99 *> \param[in] A
100 *> \verbatim
101 *> A is DOUBLE PRECISION array, dimension
102 *> (LDA,M) if SIDE = 'L',
103 *> (LDA,N) if SIDE = 'R'
104 *> The i-th row must contain the vector which defines the
105 *> elementary reflector H(i), for i = 1,2,...,k, as returned by
106 *> DTZRZF in the last k rows of its array argument A.
107 *> A is modified by the routine but restored on exit.
108 *> \endverbatim
109 *>
110 *> \param[in] LDA
111 *> \verbatim
112 *> LDA is INTEGER
113 *> The leading dimension of the array A. LDA >= max(1,K).
114 *> \endverbatim
115 *>
116 *> \param[in] TAU
117 *> \verbatim
118 *> TAU is DOUBLE PRECISION array, dimension (K)
119 *> TAU(i) must contain the scalar factor of the elementary
120 *> reflector H(i), as returned by DTZRZF.
121 *> \endverbatim
122 *>
123 *> \param[in,out] C
124 *> \verbatim
125 *> C is DOUBLE PRECISION array, dimension (LDC,N)
126 *> On entry, the M-by-N matrix C.
127 *> On exit, C is overwritten by Q*C or Q**H*C or C*Q**H or C*Q.
128 *> \endverbatim
129 *>
130 *> \param[in] LDC
131 *> \verbatim
132 *> LDC is INTEGER
133 *> The leading dimension of the array C. LDC >= max(1,M).
134 *> \endverbatim
135 *>
136 *> \param[out] WORK
137 *> \verbatim
138 *> WORK is DOUBLE PRECISION array, dimension (MAX(1,LWORK))
139 *> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
140 *> \endverbatim
141 *>
142 *> \param[in] LWORK
143 *> \verbatim
144 *> LWORK is INTEGER
145 *> The dimension of the array WORK.
146 *> If SIDE = 'L', LWORK >= max(1,N);
147 *> if SIDE = 'R', LWORK >= max(1,M).
148 *> For optimum performance LWORK >= N*NB if SIDE = 'L', and
149 *> LWORK >= M*NB if SIDE = 'R', where NB is the optimal
150 *> blocksize.
151 *>
152 *> If LWORK = -1, then a workspace query is assumed; the routine
153 *> only calculates the optimal size of the WORK array, returns
154 *> this value as the first entry of the WORK array, and no error
155 *> message related to LWORK is issued by XERBLA.
156 *> \endverbatim
157 *>
158 *> \param[out] INFO
159 *> \verbatim
160 *> INFO is INTEGER
161 *> = 0: successful exit
162 *> < 0: if INFO = -i, the i-th argument had an illegal value
163 *> \endverbatim
164 *
165 * Authors:
166 * ========
167 *
168 *> \author Univ. of Tennessee
169 *> \author Univ. of California Berkeley
170 *> \author Univ. of Colorado Denver
171 *> \author NAG Ltd.
172 *
173 *> \date November 2011
174 *
175 *> \ingroup doubleOTHERcomputational
176 *
177 *> \par Contributors:
178 * ==================
179 *>
180 *> A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
181 *
182 *> \par Further Details:
183 * =====================
184 *>
185 *> \verbatim
186 *> \endverbatim
187 *>
188 * =====================================================================
189  SUBROUTINE dormrz( SIDE, TRANS, M, N, K, L, A, LDA, TAU, C, LDC,
190  $ work, lwork, info )
191 *
192 * -- LAPACK computational routine (version 3.4.0) --
193 * -- LAPACK is a software package provided by Univ. of Tennessee, --
194 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
195 * November 2011
196 *
197 * .. Scalar Arguments ..
198  CHARACTER side, trans
199  INTEGER info, k, l, lda, ldc, lwork, m, n
200 * ..
201 * .. Array Arguments ..
202  DOUBLE PRECISION a( lda, * ), c( ldc, * ), tau( * ), work( * )
203 * ..
204 *
205 * =====================================================================
206 *
207 * .. Parameters ..
208  INTEGER nbmax, ldt
209  parameter( nbmax = 64, ldt = nbmax+1 )
210 * ..
211 * .. Local Scalars ..
212  LOGICAL left, lquery, notran
213  CHARACTER transt
214  INTEGER i, i1, i2, i3, ib, ic, iinfo, iws, ja, jc,
215  $ ldwork, lwkopt, mi, nb, nbmin, ni, nq, nw
216 * ..
217 * .. Local Arrays ..
218  DOUBLE PRECISION t( ldt, nbmax )
219 * ..
220 * .. External Functions ..
221  LOGICAL lsame
222  INTEGER ilaenv
223  EXTERNAL lsame, ilaenv
224 * ..
225 * .. External Subroutines ..
226  EXTERNAL dlarzb, dlarzt, dormr3, xerbla
227 * ..
228 * .. Intrinsic Functions ..
229  INTRINSIC max, min
230 * ..
231 * .. Executable Statements ..
232 *
233 * Test the input arguments
234 *
235  info = 0
236  left = lsame( side, 'L' )
237  notran = lsame( trans, 'N' )
238  lquery = ( lwork.EQ.-1 )
239 *
240 * NQ is the order of Q and NW is the minimum dimension of WORK
241 *
242  IF( left ) THEN
243  nq = m
244  nw = max( 1, n )
245  ELSE
246  nq = n
247  nw = max( 1, m )
248  END IF
249  IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
250  info = -1
251  ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'T' ) ) THEN
252  info = -2
253  ELSE IF( m.LT.0 ) THEN
254  info = -3
255  ELSE IF( n.LT.0 ) THEN
256  info = -4
257  ELSE IF( k.LT.0 .OR. k.GT.nq ) THEN
258  info = -5
259  ELSE IF( l.LT.0 .OR. ( left .AND. ( l.GT.m ) ) .OR.
260  $ ( .NOT.left .AND. ( l.GT.n ) ) ) THEN
261  info = -6
262  ELSE IF( lda.LT.max( 1, k ) ) THEN
263  info = -8
264  ELSE IF( ldc.LT.max( 1, m ) ) THEN
265  info = -11
266  END IF
267 *
268  IF( info.EQ.0 ) THEN
269  IF( m.EQ.0 .OR. n.EQ.0 ) THEN
270  lwkopt = 1
271  ELSE
272 *
273 * Determine the block size. NB may be at most NBMAX, where
274 * NBMAX is used to define the local array T.
275 *
276  nb = min( nbmax, ilaenv( 1, 'DORMRQ', side // trans, m, n,
277  $ k, -1 ) )
278  lwkopt = nw*nb
279  END IF
280  work( 1 ) = lwkopt
281 *
282  IF( lwork.LT.max( 1, nw ) .AND. .NOT.lquery ) THEN
283  info = -13
284  END IF
285  END IF
286 *
287  IF( info.NE.0 ) THEN
288  CALL xerbla( 'DORMRZ', -info )
289  return
290  ELSE IF( lquery ) THEN
291  return
292  END IF
293 *
294 * Quick return if possible
295 *
296  IF( m.EQ.0 .OR. n.EQ.0 ) THEN
297  work( 1 ) = 1
298  return
299  END IF
300 *
301  nbmin = 2
302  ldwork = nw
303  IF( nb.GT.1 .AND. nb.LT.k ) THEN
304  iws = nw*nb
305  IF( lwork.LT.iws ) THEN
306  nb = lwork / ldwork
307  nbmin = max( 2, ilaenv( 2, 'DORMRQ', side // trans, m, n, k,
308  $ -1 ) )
309  END IF
310  ELSE
311  iws = nw
312  END IF
313 *
314  IF( nb.LT.nbmin .OR. nb.GE.k ) THEN
315 *
316 * Use unblocked code
317 *
318  CALL dormr3( side, trans, m, n, k, l, a, lda, tau, c, ldc,
319  $ work, iinfo )
320  ELSE
321 *
322 * Use blocked code
323 *
324  IF( ( left .AND. .NOT.notran ) .OR.
325  $ ( .NOT.left .AND. notran ) ) THEN
326  i1 = 1
327  i2 = k
328  i3 = nb
329  ELSE
330  i1 = ( ( k-1 ) / nb )*nb + 1
331  i2 = 1
332  i3 = -nb
333  END IF
334 *
335  IF( left ) THEN
336  ni = n
337  jc = 1
338  ja = m - l + 1
339  ELSE
340  mi = m
341  ic = 1
342  ja = n - l + 1
343  END IF
344 *
345  IF( notran ) THEN
346  transt = 'T'
347  ELSE
348  transt = 'N'
349  END IF
350 *
351  DO 10 i = i1, i2, i3
352  ib = min( nb, k-i+1 )
353 *
354 * Form the triangular factor of the block reflector
355 * H = H(i+ib-1) . . . H(i+1) H(i)
356 *
357  CALL dlarzt( 'Backward', 'Rowwise', l, ib, a( i, ja ), lda,
358  $ tau( i ), t, ldt )
359 *
360  IF( left ) THEN
361 *
362 * H or H**T is applied to C(i:m,1:n)
363 *
364  mi = m - i + 1
365  ic = i
366  ELSE
367 *
368 * H or H**T is applied to C(1:m,i:n)
369 *
370  ni = n - i + 1
371  jc = i
372  END IF
373 *
374 * Apply H or H**T
375 *
376  CALL dlarzb( side, transt, 'Backward', 'Rowwise', mi, ni,
377  $ ib, l, a( i, ja ), lda, t, ldt, c( ic, jc ),
378  $ ldc, work, ldwork )
379  10 continue
380 *
381  END IF
382 *
383  work( 1 ) = lwkopt
384 *
385  return
386 *
387 * End of DORMRZ
388 *
389  END