LAPACK 3.12.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 REAL SROUNDUP_LWORK
203 EXTERNAL ilaenv, lsame, sroundup_lwork
204* ..
205* .. External Subroutines ..
206 EXTERNAL sormqr, xerbla
207* ..
208* .. Intrinsic Functions ..
209 INTRINSIC max, min
210* ..
211* .. Executable Statements ..
212*
213* Test the input arguments
214*
215 info = 0
216 nh = ihi - ilo
217 left = lsame( side, 'L' )
218 lquery = ( lwork.EQ.-1 )
219*
220* NQ is the order of Q and NW is the minimum dimension of WORK
221*
222 IF( left ) THEN
223 nq = m
224 nw = max( 1, n )
225 ELSE
226 nq = n
227 nw = max( 1, m )
228 END IF
229 IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
230 info = -1
231 ELSE IF( .NOT.lsame( trans, 'N' ) .AND. .NOT.lsame( trans, 'T' ) )
232 $ THEN
233 info = -2
234 ELSE IF( m.LT.0 ) THEN
235 info = -3
236 ELSE IF( n.LT.0 ) THEN
237 info = -4
238 ELSE IF( ilo.LT.1 .OR. ilo.GT.max( 1, nq ) ) THEN
239 info = -5
240 ELSE IF( ihi.LT.min( ilo, nq ) .OR. ihi.GT.nq ) THEN
241 info = -6
242 ELSE IF( lda.LT.max( 1, nq ) ) THEN
243 info = -8
244 ELSE IF( ldc.LT.max( 1, m ) ) THEN
245 info = -11
246 ELSE IF( lwork.LT.nw .AND. .NOT.lquery ) THEN
247 info = -13
248 END IF
249*
250 IF( info.EQ.0 ) THEN
251 IF( left ) THEN
252 nb = ilaenv( 1, 'SORMQR', side // trans, nh, n, nh, -1 )
253 ELSE
254 nb = ilaenv( 1, 'SORMQR', side // trans, m, nh, nh, -1 )
255 END IF
256 lwkopt = nw*nb
257 work( 1 ) = sroundup_lwork(lwkopt)
258 END IF
259*
260 IF( info.NE.0 ) THEN
261 CALL xerbla( 'SORMHR', -info )
262 RETURN
263 ELSE IF( lquery ) THEN
264 RETURN
265 END IF
266*
267* Quick return if possible
268*
269 IF( m.EQ.0 .OR. n.EQ.0 .OR. nh.EQ.0 ) THEN
270 work( 1 ) = 1
271 RETURN
272 END IF
273*
274 IF( left ) THEN
275 mi = nh
276 ni = n
277 i1 = ilo + 1
278 i2 = 1
279 ELSE
280 mi = m
281 ni = nh
282 i1 = 1
283 i2 = ilo + 1
284 END IF
285*
286 CALL sormqr( side, trans, mi, ni, nh, a( ilo+1, ilo ), lda,
287 $ tau( ilo ), c( i1, i2 ), ldc, work, lwork, iinfo )
288*
289 work( 1 ) = sroundup_lwork(lwkopt)
290 RETURN
291*
292* End of SORMHR
293*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:162
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
real function sroundup_lwork(lwork)
SROUNDUP_LWORK
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: