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

◆ zunmql()

subroutine zunmql ( 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 
)

ZUNMQL

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

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

 as returned by ZGEQLF. 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
          ZGEQLF in the last 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 ZGEQLF.
[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.

Definition at line 165 of file zunmql.f.

167*
168* -- LAPACK computational routine --
169* -- LAPACK is a software package provided by Univ. of Tennessee, --
170* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
171*
172* .. Scalar Arguments ..
173 CHARACTER SIDE, TRANS
174 INTEGER INFO, K, LDA, LDC, LWORK, M, N
175* ..
176* .. Array Arguments ..
177 COMPLEX*16 A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
178* ..
179*
180* =====================================================================
181*
182* .. Parameters ..
183 INTEGER NBMAX, LDT, TSIZE
184 parameter( nbmax = 64, ldt = nbmax+1,
185 $ tsize = ldt*nbmax )
186* ..
187* .. Local Scalars ..
188 LOGICAL LEFT, LQUERY, NOTRAN
189 INTEGER I, I1, I2, I3, IB, IINFO, IWT, LDWORK, LWKOPT,
190 $ MI, NB, NBMIN, NI, NQ, NW
191* ..
192* .. External Functions ..
193 LOGICAL LSAME
194 INTEGER ILAENV
195 EXTERNAL lsame, ilaenv
196* ..
197* .. External Subroutines ..
198 EXTERNAL xerbla, zlarfb, zlarft, zunm2l
199* ..
200* .. Intrinsic Functions ..
201 INTRINSIC max, min
202* ..
203* .. Executable Statements ..
204*
205* Test the input arguments
206*
207 info = 0
208 left = lsame( side, 'L' )
209 notran = lsame( trans, 'N' )
210 lquery = ( lwork.EQ.-1 )
211*
212* NQ is the order of Q and NW is the minimum dimension of WORK
213*
214 IF( left ) THEN
215 nq = m
216 nw = max( 1, n )
217 ELSE
218 nq = n
219 nw = max( 1, m )
220 END IF
221 IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
222 info = -1
223 ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'C' ) ) THEN
224 info = -2
225 ELSE IF( m.LT.0 ) THEN
226 info = -3
227 ELSE IF( n.LT.0 ) THEN
228 info = -4
229 ELSE IF( k.LT.0 .OR. k.GT.nq ) THEN
230 info = -5
231 ELSE IF( lda.LT.max( 1, nq ) ) THEN
232 info = -7
233 ELSE IF( ldc.LT.max( 1, m ) ) THEN
234 info = -10
235 ELSE IF( lwork.LT.nw .AND. .NOT.lquery ) THEN
236 info = -12
237 END IF
238*
239 IF( info.EQ.0 ) THEN
240*
241* Compute the workspace requirements
242*
243 IF( m.EQ.0 .OR. n.EQ.0 ) THEN
244 lwkopt = 1
245 ELSE
246 nb = min( nbmax, ilaenv( 1, 'ZUNMQL', side // trans, m, n,
247 $ k, -1 ) )
248 lwkopt = nw*nb + tsize
249 END IF
250 work( 1 ) = lwkopt
251 END IF
252*
253 IF( info.NE.0 ) THEN
254 CALL xerbla( 'ZUNMQL', -info )
255 RETURN
256 ELSE IF( lquery ) THEN
257 RETURN
258 END IF
259*
260* Quick return if possible
261*
262 IF( m.EQ.0 .OR. n.EQ.0 ) THEN
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.lwkopt ) THEN
270 nb = (lwork-tsize) / ldwork
271 nbmin = max( 2, ilaenv( 2, 'ZUNMQL', 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 zunm2l( 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. notran ) .OR.
288 $ ( .NOT.left .AND. .NOT.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 ELSE
301 mi = m
302 END IF
303*
304 DO 10 i = i1, i2, i3
305 ib = min( nb, k-i+1 )
306*
307* Form the triangular factor of the block reflector
308* H = H(i+ib-1) . . . H(i+1) H(i)
309*
310 CALL zlarft( 'Backward', 'Columnwise', nq-k+i+ib-1, ib,
311 $ a( 1, i ), lda, tau( i ), work( iwt ), ldt )
312 IF( left ) THEN
313*
314* H or H**H is applied to C(1:m-k+i+ib-1,1:n)
315*
316 mi = m - k + i + ib - 1
317 ELSE
318*
319* H or H**H is applied to C(1:m,1:n-k+i+ib-1)
320*
321 ni = n - k + i + ib - 1
322 END IF
323*
324* Apply H or H**H
325*
326 CALL zlarfb( side, trans, 'Backward', 'Columnwise', mi, ni,
327 $ ib, a( 1, i ), lda, work( iwt ), ldt, c, ldc,
328 $ work, ldwork )
329 10 CONTINUE
330 END IF
331 work( 1 ) = lwkopt
332 RETURN
333*
334* End of ZUNMQL
335*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:162
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 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:163
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine zunm2l(side, trans, m, n, k, a, lda, tau, c, ldc, work, info)
ZUNM2L multiplies a general matrix by the unitary matrix from a QL factorization determined by cgeqlf...
Definition zunm2l.f:159
Here is the call graph for this function:
Here is the caller graph for this function: