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

◆ sormlq()

subroutine sormlq ( 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 
)

SORMLQ

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

Purpose:
 SORMLQ 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(k) . . . H(2) H(1)

 as returned by SGELQF. 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,M) if SIDE = 'L',
                               (LDA,N) if SIDE = 'R'
          The i-th row must contain the vector which defines the
          elementary reflector H(i), for i = 1,2,...,k, as returned by
          SGELQF in the first k rows of its array argument A.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A. LDA >= max(1,K).
[in]TAU
          TAU is REAL array, dimension (K)
          TAU(i) must contain the scalar factor of the elementary
          reflector H(i), as returned by SGELQF.
[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 sormlq.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 CHARACTER TRANST
192 INTEGER I, I1, I2, I3, IB, IC, IINFO, IWT, JC, LDWORK,
193 $ LWKOPT, MI, NB, NBMIN, NI, NQ, NW
194* ..
195* .. External Functions ..
196 LOGICAL LSAME
197 INTEGER ILAENV
198 REAL SROUNDUP_LWORK
199 EXTERNAL lsame, ilaenv, sroundup_lwork
200* ..
201* .. External Subroutines ..
202 EXTERNAL slarfb, slarft, sorml2, xerbla
203* ..
204* .. Intrinsic Functions ..
205 INTRINSIC max, min
206* ..
207* .. Executable Statements ..
208*
209* Test the input arguments
210*
211 info = 0
212 left = lsame( side, 'L' )
213 notran = lsame( trans, 'N' )
214 lquery = ( lwork.EQ.-1 )
215*
216* NQ is the order of Q and NW is the minimum dimension of WORK
217*
218 IF( left ) THEN
219 nq = m
220 nw = max( 1, n )
221 ELSE
222 nq = n
223 nw = max( 1, m )
224 END IF
225 IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
226 info = -1
227 ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'T' ) ) THEN
228 info = -2
229 ELSE IF( m.LT.0 ) THEN
230 info = -3
231 ELSE IF( n.LT.0 ) THEN
232 info = -4
233 ELSE IF( k.LT.0 .OR. k.GT.nq ) THEN
234 info = -5
235 ELSE IF( lda.LT.max( 1, k ) ) THEN
236 info = -7
237 ELSE IF( ldc.LT.max( 1, m ) ) THEN
238 info = -10
239 ELSE IF( lwork.LT.nw .AND. .NOT.lquery ) THEN
240 info = -12
241 END IF
242*
243 IF( info.EQ.0 ) THEN
244*
245* Compute the workspace requirements
246*
247 nb = min( nbmax, ilaenv( 1, 'SORMLQ', side // trans, m, n, k,
248 $ -1 ) )
249 lwkopt = nw*nb + tsize
250 work( 1 ) = sroundup_lwork(lwkopt)
251 END IF
252*
253 IF( info.NE.0 ) THEN
254 CALL xerbla( 'SORMLQ', -info )
255 RETURN
256 ELSE IF( lquery ) THEN
257 RETURN
258 END IF
259*
260* Quick return if possible
261*
262 IF( m.EQ.0 .OR. n.EQ.0 .OR. k.EQ.0 ) THEN
263 work( 1 ) = 1
264 RETURN
265 END IF
266*
267 nbmin = 2
268 ldwork = nw
269 IF( nb.GT.1 .AND. nb.LT.k ) THEN
270 IF( lwork.LT.lwkopt ) THEN
271 nb = (lwork-tsize) / ldwork
272 nbmin = max( 2, ilaenv( 2, 'SORMLQ', side // trans, m, n, k,
273 $ -1 ) )
274 END IF
275 END IF
276*
277 IF( nb.LT.nbmin .OR. nb.GE.k ) THEN
278*
279* Use unblocked code
280*
281 CALL sorml2( side, trans, m, n, k, a, lda, tau, c, ldc, work,
282 $ iinfo )
283 ELSE
284*
285* Use blocked code
286*
287 iwt = 1 + nw*nb
288 IF( ( left .AND. notran ) .OR.
289 $ ( .NOT.left .AND. .NOT.notran ) ) THEN
290 i1 = 1
291 i2 = k
292 i3 = nb
293 ELSE
294 i1 = ( ( k-1 ) / nb )*nb + 1
295 i2 = 1
296 i3 = -nb
297 END IF
298*
299 IF( left ) THEN
300 ni = n
301 jc = 1
302 ELSE
303 mi = m
304 ic = 1
305 END IF
306*
307 IF( notran ) THEN
308 transt = 'T'
309 ELSE
310 transt = 'N'
311 END IF
312*
313 DO 10 i = i1, i2, i3
314 ib = min( nb, k-i+1 )
315*
316* Form the triangular factor of the block reflector
317* H = H(i) H(i+1) . . . H(i+ib-1)
318*
319 CALL slarft( 'Forward', 'Rowwise', nq-i+1, ib, a( i, i ),
320 $ lda, tau( i ), work( iwt ), ldt )
321 IF( left ) THEN
322*
323* H or H**T is applied to C(i:m,1:n)
324*
325 mi = m - i + 1
326 ic = i
327 ELSE
328*
329* H or H**T is applied to C(1:m,i:n)
330*
331 ni = n - i + 1
332 jc = i
333 END IF
334*
335* Apply H or H**T
336*
337 CALL slarfb( side, transt, 'Forward', 'Rowwise', mi, ni, ib,
338 $ a( i, i ), lda, work( iwt ), ldt,
339 $ c( ic, jc ), ldc, work, ldwork )
340 10 CONTINUE
341 END IF
342 work( 1 ) = sroundup_lwork(lwkopt)
343 RETURN
344*
345* End of SORMLQ
346*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:162
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
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
real function sroundup_lwork(lwork)
SROUNDUP_LWORK
subroutine sorml2(side, trans, m, n, k, a, lda, tau, c, ldc, work, info)
SORML2 multiplies a general matrix by the orthogonal matrix from a LQ factorization determined by sge...
Definition sorml2.f:159
Here is the call graph for this function:
Here is the caller graph for this function: