LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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.
Date
November 2011

Definition at line 173 of file zunmtr.f.

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

Here is the call graph for this function:

Here is the caller graph for this function: