LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine sormtr ( character  SIDE,
character  UPLO,
character  TRANS,
integer  M,
integer  N,
real, dimension( lda, * )  A,
integer  LDA,
real, dimension( * )  TAU,
real, dimension( ldc, * )  C,
integer  LDC,
real, dimension( * )  WORK,
integer  LWORK,
integer  INFO 
)

SORMTR

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

Purpose:
 SORMTR overwrites the general real M-by-N matrix C with

                 SIDE = 'L'     SIDE = 'R'
 TRANS = 'N':      Q * C          C * Q
 TRANS = 'T':      Q**T * C       C * Q**T

 where Q is a real orthogonal 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 SSYTRD:

 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**T from the Left;
          = 'R': apply Q or Q**T from the Right.
[in]UPLO
          UPLO is CHARACTER*1
          = 'U': Upper triangle of A contains elementary reflectors
                 from SSYTRD;
          = 'L': Lower triangle of A contains elementary reflectors
                 from SSYTRD.
[in]TRANS
          TRANS is CHARACTER*1
          = 'N':  No transpose, apply Q;
          = 'T':  Transpose, apply Q**T.
[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 REAL array, dimension
                               (LDA,M) if SIDE = 'L'
                               (LDA,N) if SIDE = 'R'
          The vectors which define the elementary reflectors, as
          returned by SSYTRD.
[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 REAL 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 SSYTRD.
[in,out]C
          C is REAL array, dimension (LDC,N)
          On entry, the M-by-N matrix C.
          On exit, C is overwritten by Q*C or Q**T*C or C*Q**T or C*Q.
[in]LDC
          LDC is INTEGER
          The leading dimension of the array C. LDC >= max(1,M).
[out]WORK
          WORK is REAL 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 174 of file sormtr.f.

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