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

◆ zunmtr()

subroutine zunmtr ( character  side,
character  uplo,
character  trans,
integer  m,
integer  n,
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 
)

ZUNMTR

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

Purpose:
 ZUNMTR 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 of order nq, with nq = m if
 SIDE = 'L' and nq = n if SIDE = 'R'. Q is defined as the product of
 nq-1 elementary reflectors, as returned by ZHETRD:

 if UPLO = 'U', Q = H(nq-1) . . . H(2) H(1);

 if UPLO = 'L', Q = H(1) H(2) . . . H(nq-1).
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]UPLO
          UPLO is CHARACTER*1
          = 'U': Upper triangle of A contains elementary reflectors
                 from ZHETRD;
          = 'L': Lower triangle of A contains elementary reflectors
                 from ZHETRD.
[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]A
          A is COMPLEX*16 array, dimension
                               (LDA,M) if SIDE = 'L'
                               (LDA,N) if SIDE = 'R'
          The vectors which define the elementary reflectors, as
          returned by ZHETRD.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.
          LDA >= max(1,M) if SIDE = 'L'; LDA >= max(1,N) if SIDE = 'R'.
[in]TAU
          TAU is COMPLEX*16 array, dimension
                               (M-1) if SIDE = 'L'
                               (N-1) if SIDE = 'R'
          TAU(i) must contain the scalar factor of the elementary
          reflector H(i), as returned by ZHETRD.
[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 optimum performance LWORK >= N*NB if SIDE = 'L', and
          LWORK >=M*NB if SIDE = 'R', where NB is the optimal
          blocksize.

          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 169 of file zunmtr.f.

171*
172* -- LAPACK computational routine --
173* -- LAPACK is a software package provided by Univ. of Tennessee, --
174* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
175*
176* .. Scalar Arguments ..
177 CHARACTER SIDE, TRANS, UPLO
178 INTEGER INFO, LDA, LDC, LWORK, M, N
179* ..
180* .. Array Arguments ..
181 COMPLEX*16 A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
182* ..
183*
184* =====================================================================
185*
186* .. Local Scalars ..
187 LOGICAL LEFT, LQUERY, UPPER
188 INTEGER I1, I2, IINFO, LWKOPT, MI, NB, NI, NQ, NW
189* ..
190* .. External Functions ..
191 LOGICAL LSAME
192 INTEGER ILAENV
193 EXTERNAL lsame, ilaenv
194* ..
195* .. External Subroutines ..
196 EXTERNAL xerbla, zunmql, zunmqr
197* ..
198* .. Intrinsic Functions ..
199 INTRINSIC max
200* ..
201* .. Executable Statements ..
202*
203* Test the input arguments
204*
205 info = 0
206 left = lsame( side, 'L' )
207 upper = lsame( uplo, 'U' )
208 lquery = ( lwork.EQ.-1 )
209*
210* NQ is the order of Q and NW is the minimum dimension of WORK
211*
212 IF( left ) THEN
213 nq = m
214 nw = max( 1, n )
215 ELSE
216 nq = n
217 nw = max( 1, m )
218 END IF
219 IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
220 info = -1
221 ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
222 info = -2
223 ELSE IF( .NOT.lsame( trans, 'N' ) .AND. .NOT.lsame( trans, 'C' ) )
224 $ THEN
225 info = -3
226 ELSE IF( m.LT.0 ) THEN
227 info = -4
228 ELSE IF( n.LT.0 ) THEN
229 info = -5
230 ELSE IF( lda.LT.max( 1, nq ) ) THEN
231 info = -7
232 ELSE IF( ldc.LT.max( 1, m ) ) THEN
233 info = -10
234 ELSE IF( lwork.LT.nw .AND. .NOT.lquery ) THEN
235 info = -12
236 END IF
237*
238 IF( info.EQ.0 ) THEN
239 IF( upper ) THEN
240 IF( left ) THEN
241 nb = ilaenv( 1, 'ZUNMQL', side // trans, m-1, n, m-1,
242 $ -1 )
243 ELSE
244 nb = ilaenv( 1, 'ZUNMQL', side // trans, m, n-1, n-1,
245 $ -1 )
246 END IF
247 ELSE
248 IF( left ) THEN
249 nb = ilaenv( 1, 'ZUNMQR', side // trans, m-1, n, m-1,
250 $ -1 )
251 ELSE
252 nb = ilaenv( 1, 'ZUNMQR', side // trans, m, n-1, n-1,
253 $ -1 )
254 END IF
255 END IF
256 lwkopt = nw*nb
257 work( 1 ) = lwkopt
258 END IF
259*
260 IF( info.NE.0 ) THEN
261 CALL xerbla( 'ZUNMTR', -info )
262 RETURN
263 ELSE IF( lquery ) THEN
264 RETURN
265 END IF
266*
267* Quick return if possible
268*
269 IF( m.EQ.0 .OR. n.EQ.0 .OR. nq.EQ.1 ) THEN
270 work( 1 ) = 1
271 RETURN
272 END IF
273*
274 IF( left ) THEN
275 mi = m - 1
276 ni = n
277 ELSE
278 mi = m
279 ni = n - 1
280 END IF
281*
282 IF( upper ) THEN
283*
284* Q was determined by a call to ZHETRD with UPLO = 'U'
285*
286 CALL zunmql( side, trans, mi, ni, nq-1, a( 1, 2 ), lda, tau, c,
287 $ ldc, work, lwork, iinfo )
288 ELSE
289*
290* Q was determined by a call to ZHETRD with UPLO = 'L'
291*
292 IF( left ) THEN
293 i1 = 2
294 i2 = 1
295 ELSE
296 i1 = 1
297 i2 = 2
298 END IF
299 CALL zunmqr( side, trans, mi, ni, nq-1, a( 2, 1 ), lda, tau,
300 $ c( i1, i2 ), ldc, work, lwork, iinfo )
301 END IF
302 work( 1 ) = lwkopt
303 RETURN
304*
305* End of ZUNMTR
306*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:162
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine zunmql(side, trans, m, n, k, a, lda, tau, c, ldc, work, lwork, info)
ZUNMQL
Definition zunmql.f:167
subroutine zunmqr(side, trans, m, n, k, a, lda, tau, c, ldc, work, lwork, info)
ZUNMQR
Definition zunmqr.f:167
Here is the call graph for this function:
Here is the caller graph for this function: