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

◆ dormhr()

subroutine dormhr ( character  side,
character  trans,
integer  m,
integer  n,
integer  ilo,
integer  ihi,
double precision, dimension( lda, * )  a,
integer  lda,
double precision, dimension( * )  tau,
double precision, dimension( ldc, * )  c,
integer  ldc,
double precision, dimension( * )  work,
integer  lwork,
integer  info 
)

DORMHR

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

Purpose:
 DORMHR 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 DGEHRD:

 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 DGEHRD. 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 DOUBLE PRECISION array, dimension
                               (LDA,M) if SIDE = 'L'
                               (LDA,N) if SIDE = 'R'
          The vectors which define the elementary reflectors, as
          returned by DGEHRD.
[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 DOUBLE PRECISION 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 DGEHRD.
[in,out]C
          C is DOUBLE PRECISION 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 DOUBLE PRECISION 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 176 of file dormhr.f.

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