LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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.
Date
November 2015

Definition at line 170 of file sormqr.f.

170 *
171 * -- LAPACK computational routine (version 3.6.0) --
172 * -- LAPACK is a software package provided by Univ. of Tennessee, --
173 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
174 * November 2015
175 *
176 * .. Scalar Arguments ..
177  CHARACTER side, trans
178  INTEGER info, k, lda, ldc, lwork, m, n
179 * ..
180 * .. Array Arguments ..
181  REAL a( lda, * ), c( ldc, * ), tau( * ),
182  $ work( * )
183 * ..
184 *
185 * =====================================================================
186 *
187 * .. Parameters ..
188  INTEGER nbmax, ldt, tsize
189  parameter ( nbmax = 64, ldt = nbmax+1,
190  $ tsize = ldt*nbmax )
191 * ..
192 * .. Local Scalars ..
193  LOGICAL left, lquery, notran
194  INTEGER i, i1, i2, i3, ib, ic, iinfo, iwt, jc, ldwork,
195  $ lwkopt, mi, nb, nbmin, ni, nq, nw
196 * ..
197 * .. External Functions ..
198  LOGICAL lsame
199  INTEGER ilaenv
200  EXTERNAL lsame, ilaenv
201 * ..
202 * .. External Subroutines ..
203  EXTERNAL slarfb, slarft, sorm2r, xerbla
204 * ..
205 * .. Intrinsic Functions ..
206  INTRINSIC max, min
207 * ..
208 * .. Executable Statements ..
209 *
210 * Test the input arguments
211 *
212  info = 0
213  left = lsame( side, 'L' )
214  notran = lsame( trans, 'N' )
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 = n
222  ELSE
223  nq = n
224  nw = m
225  END IF
226  IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
227  info = -1
228  ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'T' ) ) THEN
229  info = -2
230  ELSE IF( m.LT.0 ) THEN
231  info = -3
232  ELSE IF( n.LT.0 ) THEN
233  info = -4
234  ELSE IF( k.LT.0 .OR. k.GT.nq ) THEN
235  info = -5
236  ELSE IF( lda.LT.max( 1, nq ) ) THEN
237  info = -7
238  ELSE IF( ldc.LT.max( 1, m ) ) THEN
239  info = -10
240  ELSE IF( lwork.LT.max( 1, nw ) .AND. .NOT.lquery ) THEN
241  info = -12
242  END IF
243 *
244  IF( info.EQ.0 ) THEN
245 *
246 * Compute the workspace requirements
247 *
248  nb = min( nbmax, ilaenv( 1, 'SORMQR', side // trans, m, n, k,
249  $ -1 ) )
250  lwkopt = max( 1, nw )*nb + tsize
251  work( 1 ) = lwkopt
252  END IF
253 *
254  IF( info.NE.0 ) THEN
255  CALL xerbla( 'SORMQR', -info )
256  RETURN
257  ELSE IF( lquery ) THEN
258  RETURN
259  END IF
260 *
261 * Quick return if possible
262 *
263  IF( m.EQ.0 .OR. n.EQ.0 .OR. k.EQ.0 ) THEN
264  work( 1 ) = 1
265  RETURN
266  END IF
267 *
268  nbmin = 2
269  ldwork = nw
270  IF( nb.GT.1 .AND. nb.LT.k ) THEN
271  IF( lwork.LT.nw*nb+tsize ) THEN
272  nb = (lwork-tsize) / ldwork
273  nbmin = max( 2, ilaenv( 2, 'SORMQR', side // trans, m, n, k,
274  $ -1 ) )
275  END IF
276  END IF
277 *
278  IF( nb.LT.nbmin .OR. nb.GE.k ) THEN
279 *
280 * Use unblocked code
281 *
282  CALL sorm2r( side, trans, m, n, k, a, lda, tau, c, ldc, work,
283  $ iinfo )
284  ELSE
285 *
286 * Use blocked code
287 *
288  iwt = 1 + nw*nb
289  IF( ( left .AND. .NOT.notran ) .OR.
290  $ ( .NOT.left .AND. notran ) ) THEN
291  i1 = 1
292  i2 = k
293  i3 = nb
294  ELSE
295  i1 = ( ( k-1 ) / nb )*nb + 1
296  i2 = 1
297  i3 = -nb
298  END IF
299 *
300  IF( left ) THEN
301  ni = n
302  jc = 1
303  ELSE
304  mi = m
305  ic = 1
306  END IF
307 *
308  DO 10 i = i1, i2, i3
309  ib = min( nb, k-i+1 )
310 *
311 * Form the triangular factor of the block reflector
312 * H = H(i) H(i+1) . . . H(i+ib-1)
313 *
314  CALL slarft( 'Forward', 'Columnwise', nq-i+1, ib, a( i, i ),
315  $ lda, tau( i ), work( iwt ), ldt )
316  IF( left ) THEN
317 *
318 * H or H**T is applied to C(i:m,1:n)
319 *
320  mi = m - i + 1
321  ic = i
322  ELSE
323 *
324 * H or H**T is applied to C(1:m,i:n)
325 *
326  ni = n - i + 1
327  jc = i
328  END IF
329 *
330 * Apply H or H**T
331 *
332  CALL slarfb( side, trans, 'Forward', 'Columnwise', mi, ni,
333  $ ib, a( i, i ), lda, work( iwt ), ldt,
334  $ c( ic, jc ), ldc, work, ldwork )
335  10 CONTINUE
336  END IF
337  work( 1 ) = lwkopt
338  RETURN
339 *
340 * End of SORMQR
341 *
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
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:165
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 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:161
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: