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

◆ cunmtr()

subroutine cunmtr ( character  SIDE,
character  UPLO,
character  TRANS,
integer  M,
integer  N,
complex, dimension( lda, * )  A,
integer  LDA,
complex, dimension( * )  TAU,
complex, dimension( ldc, * )  C,
integer  LDC,
complex, dimension( * )  WORK,
integer  LWORK,
integer  INFO 
)

CUNMTR

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

Purpose:
 CUNMTR 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 CHETRD:

 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 CHETRD;
          = 'L': Lower triangle of A contains elementary reflectors
                 from CHETRD.
[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 array, dimension
                               (LDA,M) if SIDE = 'L'
                               (LDA,N) if SIDE = 'R'
          The vectors which define the elementary reflectors, as
          returned by CHETRD.
[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 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 CHETRD.
[in,out]C
          C is COMPLEX 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 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 170 of file cunmtr.f.

172*
173* -- LAPACK computational routine --
174* -- LAPACK is a software package provided by Univ. of Tennessee, --
175* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
176*
177* .. Scalar Arguments ..
178 CHARACTER SIDE, TRANS, UPLO
179 INTEGER INFO, LDA, LDC, LWORK, M, N
180* ..
181* .. Array Arguments ..
182 COMPLEX A( LDA, * ), C( LDC, * ), TAU( * ),
183 $ WORK( * )
184* ..
185*
186* =====================================================================
187*
188* .. Local Scalars ..
189 LOGICAL LEFT, LQUERY, UPPER
190 INTEGER I1, I2, IINFO, LWKOPT, MI, NB, NI, NQ, NW
191* ..
192* .. External Functions ..
193 LOGICAL LSAME
194 INTEGER ILAENV
195 EXTERNAL ilaenv, lsame
196* ..
197* .. External Subroutines ..
198 EXTERNAL cunmql, cunmqr, xerbla
199* ..
200* .. Intrinsic Functions ..
201 INTRINSIC max
202* ..
203* .. Executable Statements ..
204*
205* Test the input arguments
206*
207 info = 0
208 left = lsame( side, 'L' )
209 upper = lsame( uplo, 'U' )
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.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
224 info = -2
225 ELSE IF( .NOT.lsame( trans, 'N' ) .AND. .NOT.lsame( trans, 'C' ) )
226 $ THEN
227 info = -3
228 ELSE IF( m.LT.0 ) THEN
229 info = -4
230 ELSE IF( n.LT.0 ) THEN
231 info = -5
232 ELSE IF( lda.LT.max( 1, nq ) ) THEN
233 info = -7
234 ELSE IF( ldc.LT.max( 1, m ) ) THEN
235 info = -10
236 ELSE IF( lwork.LT.nw .AND. .NOT.lquery ) THEN
237 info = -12
238 END IF
239*
240 IF( info.EQ.0 ) THEN
241 IF( upper ) THEN
242 IF( left ) THEN
243 nb = ilaenv( 1, 'CUNMQL', side // trans, m-1, n, m-1,
244 $ -1 )
245 ELSE
246 nb = ilaenv( 1, 'CUNMQL', side // trans, m, n-1, n-1,
247 $ -1 )
248 END IF
249 ELSE
250 IF( left ) THEN
251 nb = ilaenv( 1, 'CUNMQR', side // trans, m-1, n, m-1,
252 $ -1 )
253 ELSE
254 nb = ilaenv( 1, 'CUNMQR', side // trans, m, n-1, n-1,
255 $ -1 )
256 END IF
257 END IF
258 lwkopt = nw*nb
259 work( 1 ) = lwkopt
260 END IF
261*
262 IF( info.NE.0 ) THEN
263 CALL xerbla( 'CUNMTR', -info )
264 RETURN
265 ELSE IF( lquery ) THEN
266 RETURN
267 END IF
268*
269* Quick return if possible
270*
271 IF( m.EQ.0 .OR. n.EQ.0 .OR. nq.EQ.1 ) THEN
272 work( 1 ) = 1
273 RETURN
274 END IF
275*
276 IF( left ) THEN
277 mi = m - 1
278 ni = n
279 ELSE
280 mi = m
281 ni = n - 1
282 END IF
283*
284 IF( upper ) THEN
285*
286* Q was determined by a call to CHETRD with UPLO = 'U'
287*
288 CALL cunmql( side, trans, mi, ni, nq-1, a( 1, 2 ), lda, tau, c,
289 $ ldc, work, lwork, iinfo )
290 ELSE
291*
292* Q was determined by a call to CHETRD with UPLO = 'L'
293*
294 IF( left ) THEN
295 i1 = 2
296 i2 = 1
297 ELSE
298 i1 = 1
299 i2 = 2
300 END IF
301 CALL cunmqr( side, trans, mi, ni, nq-1, a( 2, 1 ), lda, tau,
302 $ c( i1, i2 ), ldc, work, lwork, iinfo )
303 END IF
304 work( 1 ) = lwkopt
305 RETURN
306*
307* End of CUNMTR
308*
integer function ilaenv(ISPEC, NAME, OPTS, N1, N2, N3, N4)
ILAENV
Definition: ilaenv.f:162
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:60
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:53
subroutine cunmql(SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, LWORK, INFO)
CUNMQL
Definition: cunmql.f:168
subroutine cunmqr(SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, LWORK, INFO)
CUNMQR
Definition: cunmqr.f:168
Here is the call graph for this function:
Here is the caller graph for this function: