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

SORMHR

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

Purpose:
 SORMHR 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
 IHI-ILO elementary reflectors, as returned by SGEHRD:

 Q = H(ilo) H(ilo+1) . . . H(ihi-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]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]ILO
          ILO is INTEGER
[in]IHI
          IHI is INTEGER

          ILO and IHI must have the same values as in the previous call
          of SGEHRD. Q is equal to the unit matrix except in the
          submatrix Q(ilo+1:ihi,ilo+1:ihi).
          If SIDE = 'L', then 1 <= ILO <= IHI <= M, if M > 0, and
          ILO = 1 and IHI = 0, if M = 0;
          if SIDE = 'R', then 1 <= ILO <= IHI <= N, if N > 0, and
          ILO = 1 and IHI = 0, if 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 SGEHRD.
[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 SGEHRD.
[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 181 of file sormhr.f.

181 *
182 * -- LAPACK computational routine (version 3.4.0) --
183 * -- LAPACK is a software package provided by Univ. of Tennessee, --
184 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
185 * November 2011
186 *
187 * .. Scalar Arguments ..
188  CHARACTER side, trans
189  INTEGER ihi, ilo, info, lda, ldc, lwork, m, n
190 * ..
191 * .. Array Arguments ..
192  REAL a( lda, * ), c( ldc, * ), tau( * ),
193  $ work( * )
194 * ..
195 *
196 * =====================================================================
197 *
198 * .. Local Scalars ..
199  LOGICAL left, lquery
200  INTEGER i1, i2, iinfo, lwkopt, mi, nb, nh, ni, nq, nw
201 * ..
202 * .. External Functions ..
203  LOGICAL lsame
204  INTEGER ilaenv
205  EXTERNAL ilaenv, lsame
206 * ..
207 * .. External Subroutines ..
208  EXTERNAL sormqr, xerbla
209 * ..
210 * .. Intrinsic Functions ..
211  INTRINSIC max, min
212 * ..
213 * .. Executable Statements ..
214 *
215 * Test the input arguments
216 *
217  info = 0
218  nh = ihi - ilo
219  left = lsame( side, 'L' )
220  lquery = ( lwork.EQ.-1 )
221 *
222 * NQ is the order of Q and NW is the minimum dimension of WORK
223 *
224  IF( left ) THEN
225  nq = m
226  nw = n
227  ELSE
228  nq = n
229  nw = m
230  END IF
231  IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
232  info = -1
233  ELSE IF( .NOT.lsame( trans, 'N' ) .AND. .NOT.lsame( trans, 'T' ) )
234  $ THEN
235  info = -2
236  ELSE IF( m.LT.0 ) THEN
237  info = -3
238  ELSE IF( n.LT.0 ) THEN
239  info = -4
240  ELSE IF( ilo.LT.1 .OR. ilo.GT.max( 1, nq ) ) THEN
241  info = -5
242  ELSE IF( ihi.LT.min( ilo, nq ) .OR. ihi.GT.nq ) THEN
243  info = -6
244  ELSE IF( lda.LT.max( 1, nq ) ) THEN
245  info = -8
246  ELSE IF( ldc.LT.max( 1, m ) ) THEN
247  info = -11
248  ELSE IF( lwork.LT.max( 1, nw ) .AND. .NOT.lquery ) THEN
249  info = -13
250  END IF
251 *
252  IF( info.EQ.0 ) THEN
253  IF( left ) THEN
254  nb = ilaenv( 1, 'SORMQR', side // trans, nh, n, nh, -1 )
255  ELSE
256  nb = ilaenv( 1, 'SORMQR', side // trans, m, nh, nh, -1 )
257  END IF
258  lwkopt = max( 1, nw )*nb
259  work( 1 ) = lwkopt
260  END IF
261 *
262  IF( info.NE.0 ) THEN
263  CALL xerbla( 'SORMHR', -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. nh.EQ.0 ) THEN
272  work( 1 ) = 1
273  RETURN
274  END IF
275 *
276  IF( left ) THEN
277  mi = nh
278  ni = n
279  i1 = ilo + 1
280  i2 = 1
281  ELSE
282  mi = m
283  ni = nh
284  i1 = 1
285  i2 = ilo + 1
286  END IF
287 *
288  CALL sormqr( side, trans, mi, ni, nh, a( ilo+1, ilo ), lda,
289  $ tau( ilo ), c( i1, i2 ), ldc, work, lwork, iinfo )
290 *
291  work( 1 ) = lwkopt
292  RETURN
293 *
294 * End of SORMHR
295 *
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: