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

◆ sormhr()

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.

Definition at line 177 of file sormhr.f.

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