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

◆ sormqr()

subroutine sormqr ( character  SIDE,
character  TRANS,
integer  M,
integer  N,
integer  K,
real, dimension( lda, * )  A,
integer  LDA,
real, dimension( * )  TAU,
real, dimension( ldc, * )  C,
integer  LDC,
real, dimension( * )  WORK,
integer  LWORK,
integer  INFO 
)

SORMQR

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

Purpose:
 SORMQR 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 defined as the product of k
 elementary reflectors

       Q = H(1) H(2) . . . H(k)

 as returned by SGEQRF. Q is of order M if SIDE = 'L' and of order N
 if SIDE = 'R'.
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]K
          K is INTEGER
          The number of elementary reflectors whose product defines
          the matrix Q.
          If SIDE = 'L', M >= K >= 0;
          if SIDE = 'R', N >= K >= 0.
[in]A
          A is REAL array, dimension (LDA,K)
          The i-th column must contain the vector which defines the
          elementary reflector H(i), for i = 1,2,...,k, as returned by
          SGEQRF in the first k columns of its array argument A.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.
          If SIDE = 'L', LDA >= max(1,M);
          if SIDE = 'R', LDA >= max(1,N).
[in]TAU
          TAU is REAL array, dimension (K)
          TAU(i) must contain the scalar factor of the elementary
          reflector H(i), as returned by SGEQRF.
[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 good performance, LWORK should generally be larger.

          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 166 of file sormqr.f.

168*
169* -- LAPACK computational routine --
170* -- LAPACK is a software package provided by Univ. of Tennessee, --
171* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
172*
173* .. Scalar Arguments ..
174 CHARACTER SIDE, TRANS
175 INTEGER INFO, K, LDA, LDC, LWORK, M, N
176* ..
177* .. Array Arguments ..
178 REAL A( LDA, * ), C( LDC, * ), TAU( * ),
179 $ WORK( * )
180* ..
181*
182* =====================================================================
183*
184* .. Parameters ..
185 INTEGER NBMAX, LDT, TSIZE
186 parameter( nbmax = 64, ldt = nbmax+1,
187 $ tsize = ldt*nbmax )
188* ..
189* .. Local Scalars ..
190 LOGICAL LEFT, LQUERY, NOTRAN
191 INTEGER I, I1, I2, I3, IB, IC, IINFO, IWT, JC, LDWORK,
192 $ LWKOPT, MI, NB, NBMIN, NI, NQ, NW
193* ..
194* .. External Functions ..
195 LOGICAL LSAME
196 INTEGER ILAENV
197 EXTERNAL lsame, ilaenv
198* ..
199* .. External Subroutines ..
200 EXTERNAL slarfb, slarft, sorm2r, xerbla
201* ..
202* .. Intrinsic Functions ..
203 INTRINSIC max, min
204* ..
205* .. Executable Statements ..
206*
207* Test the input arguments
208*
209 info = 0
210 left = lsame( side, 'L' )
211 notran = lsame( trans, 'N' )
212 lquery = ( lwork.EQ.-1 )
213*
214* NQ is the order of Q and NW is the minimum dimension of WORK
215*
216 IF( left ) THEN
217 nq = m
218 nw = max( 1, n )
219 ELSE
220 nq = n
221 nw = max( 1, m )
222 END IF
223 IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
224 info = -1
225 ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'T' ) ) THEN
226 info = -2
227 ELSE IF( m.LT.0 ) THEN
228 info = -3
229 ELSE IF( n.LT.0 ) THEN
230 info = -4
231 ELSE IF( k.LT.0 .OR. k.GT.nq ) THEN
232 info = -5
233 ELSE IF( lda.LT.max( 1, nq ) ) THEN
234 info = -7
235 ELSE IF( ldc.LT.max( 1, m ) ) THEN
236 info = -10
237 ELSE IF( lwork.LT.nw .AND. .NOT.lquery ) THEN
238 info = -12
239 END IF
240*
241 IF( info.EQ.0 ) THEN
242*
243* Compute the workspace requirements
244*
245 nb = min( nbmax, ilaenv( 1, 'SORMQR', side // trans, m, n, k,
246 $ -1 ) )
247 lwkopt = nw*nb + tsize
248 work( 1 ) = lwkopt
249 END IF
250*
251 IF( info.NE.0 ) THEN
252 CALL xerbla( 'SORMQR', -info )
253 RETURN
254 ELSE IF( lquery ) THEN
255 RETURN
256 END IF
257*
258* Quick return if possible
259*
260 IF( m.EQ.0 .OR. n.EQ.0 .OR. k.EQ.0 ) THEN
261 work( 1 ) = 1
262 RETURN
263 END IF
264*
265 nbmin = 2
266 ldwork = nw
267 IF( nb.GT.1 .AND. nb.LT.k ) THEN
268 IF( lwork.LT.lwkopt ) THEN
269 nb = (lwork-tsize) / ldwork
270 nbmin = max( 2, ilaenv( 2, 'SORMQR', side // trans, m, n, k,
271 $ -1 ) )
272 END IF
273 END IF
274*
275 IF( nb.LT.nbmin .OR. nb.GE.k ) THEN
276*
277* Use unblocked code
278*
279 CALL sorm2r( side, trans, m, n, k, a, lda, tau, c, ldc, work,
280 $ iinfo )
281 ELSE
282*
283* Use blocked code
284*
285 iwt = 1 + nw*nb
286 IF( ( left .AND. .NOT.notran ) .OR.
287 $ ( .NOT.left .AND. notran ) ) THEN
288 i1 = 1
289 i2 = k
290 i3 = nb
291 ELSE
292 i1 = ( ( k-1 ) / nb )*nb + 1
293 i2 = 1
294 i3 = -nb
295 END IF
296*
297 IF( left ) THEN
298 ni = n
299 jc = 1
300 ELSE
301 mi = m
302 ic = 1
303 END IF
304*
305 DO 10 i = i1, i2, i3
306 ib = min( nb, k-i+1 )
307*
308* Form the triangular factor of the block reflector
309* H = H(i) H(i+1) . . . H(i+ib-1)
310*
311 CALL slarft( 'Forward', 'Columnwise', nq-i+1, ib, a( i, i ),
312 $ lda, tau( i ), work( iwt ), ldt )
313 IF( left ) THEN
314*
315* H or H**T is applied to C(i:m,1:n)
316*
317 mi = m - i + 1
318 ic = i
319 ELSE
320*
321* H or H**T is applied to C(1:m,i:n)
322*
323 ni = n - i + 1
324 jc = i
325 END IF
326*
327* Apply H or H**T
328*
329 CALL slarfb( side, trans, 'Forward', 'Columnwise', mi, ni,
330 $ ib, a( i, i ), lda, work( iwt ), ldt,
331 $ c( ic, jc ), ldc, work, ldwork )
332 10 CONTINUE
333 END IF
334 work( 1 ) = lwkopt
335 RETURN
336*
337* End of SORMQR
338*
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 slarfb(SIDE, TRANS, DIRECT, STOREV, M, N, K, V, LDV, T, LDT, C, LDC, WORK, LDWORK)
SLARFB applies a block reflector or its transpose to a general rectangular matrix.
Definition: slarfb.f:197
subroutine slarft(DIRECT, STOREV, N, K, V, LDV, TAU, T, LDT)
SLARFT forms the triangular factor T of a block reflector H = I - vtvH
Definition: slarft.f:163
subroutine sorm2r(SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, INFO)
SORM2R multiplies a general matrix by the orthogonal matrix from a QR factorization determined by sge...
Definition: sorm2r.f:159
Here is the call graph for this function:
Here is the caller graph for this function: