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

◆ dgemlqt()

subroutine dgemlqt ( character side,
character trans,
integer m,
integer n,
integer k,
integer mb,
double precision, dimension( ldv, * ) v,
integer ldv,
double precision, dimension( ldt, * ) t,
integer ldt,
double precision, dimension( ldc, * ) c,
integer ldc,
double precision, dimension( * ) work,
integer info )

DGEMLQT

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

Purpose:
!>
!> DGEMLQT 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) = I - V T V**T
!>
!> generated using the compact WY representation as returned by DGELQT.
!>
!> 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;
!>          = 'C':  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]MB
!>          MB is INTEGER
!>          The block size used for the storage of T.  K >= MB >= 1.
!>          This must be the same value of MB used to generate T
!>          in DGELQT.
!> 
[in]V
!>          V is DOUBLE PRECISION array, dimension
!>                               (LDV,M) if SIDE = 'L',
!>                               (LDV,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
!>          DGELQT in the first K rows of its array argument A.
!> 
[in]LDV
!>          LDV is INTEGER
!>          The leading dimension of the array V.  LDV >= max(1,K).
!> 
[in]T
!>          T is DOUBLE PRECISION array, dimension (LDT,K)
!>          The upper triangular factors of the block reflectors
!>          as returned by DGELQT, stored as a MB-by-K matrix.
!> 
[in]LDT
!>          LDT is INTEGER
!>          The leading dimension of the array T.  LDT >= MB.
!> 
[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, Q**T C, 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. The dimension of
!>          WORK is N*MB if SIDE = 'L', or  M*MB if SIDE = 'R'.
!> 
[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 164 of file dgemlqt.f.

166*
167* -- LAPACK computational routine --
168* -- LAPACK is a software package provided by Univ. of Tennessee, --
169* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
170*
171* .. Scalar Arguments ..
172 CHARACTER SIDE, TRANS
173 INTEGER INFO, K, LDV, LDC, M, N, MB, LDT
174* ..
175* .. Array Arguments ..
176 DOUBLE PRECISION V( LDV, * ), C( LDC, * ), T( LDT, * ), WORK( * )
177* ..
178*
179* =====================================================================
180*
181* ..
182* .. Local Scalars ..
183 LOGICAL LEFT, RIGHT, TRAN, NOTRAN
184 INTEGER I, IB, LDWORK, KF, Q
185* ..
186* .. External Functions ..
187 LOGICAL LSAME
188 EXTERNAL lsame
189* ..
190* .. External Subroutines ..
191 EXTERNAL xerbla, dlarfb
192* ..
193* .. Intrinsic Functions ..
194 INTRINSIC max, min
195* ..
196* .. Executable Statements ..
197*
198* .. Test the input arguments ..
199*
200 info = 0
201 left = lsame( side, 'L' )
202 right = lsame( side, 'R' )
203 tran = lsame( trans, 'T' )
204 notran = lsame( trans, 'N' )
205*
206 IF( left ) THEN
207 ldwork = max( 1, n )
208 q = m
209 ELSE IF ( right ) THEN
210 ldwork = max( 1, m )
211 q = n
212 END IF
213 IF( .NOT.left .AND. .NOT.right ) THEN
214 info = -1
215 ELSE IF( .NOT.tran .AND. .NOT.notran ) THEN
216 info = -2
217 ELSE IF( m.LT.0 ) THEN
218 info = -3
219 ELSE IF( n.LT.0 ) THEN
220 info = -4
221 ELSE IF( k.LT.0 .OR. k.GT.q ) THEN
222 info = -5
223 ELSE IF( mb.LT.1 .OR. (mb.GT.k .AND. k.GT.0)) THEN
224 info = -6
225 ELSE IF( ldv.LT.max( 1, k ) ) THEN
226 info = -8
227 ELSE IF( ldt.LT.mb ) THEN
228 info = -10
229 ELSE IF( ldc.LT.max( 1, m ) ) THEN
230 info = -12
231 END IF
232*
233 IF( info.NE.0 ) THEN
234 CALL xerbla( 'DGEMLQT', -info )
235 RETURN
236 END IF
237*
238* .. Quick return if possible ..
239*
240 IF( m.EQ.0 .OR. n.EQ.0 .OR. k.EQ.0 ) RETURN
241*
242 IF( left .AND. notran ) THEN
243*
244 DO i = 1, k, mb
245 ib = min( mb, k-i+1 )
246 CALL dlarfb( 'L', 'T', 'F', 'R', m-i+1, n, ib,
247 $ v( i, i ), ldv, t( 1, i ), ldt,
248 $ c( i, 1 ), ldc, work, ldwork )
249 END DO
250*
251 ELSE IF( right .AND. tran ) THEN
252*
253 DO i = 1, k, mb
254 ib = min( mb, k-i+1 )
255 CALL dlarfb( 'R', 'N', 'F', 'R', m, n-i+1, ib,
256 $ v( i, i ), ldv, t( 1, i ), ldt,
257 $ c( 1, i ), ldc, work, ldwork )
258 END DO
259*
260 ELSE IF( left .AND. tran ) THEN
261*
262 kf = ((k-1)/mb)*mb+1
263 DO i = kf, 1, -mb
264 ib = min( mb, k-i+1 )
265 CALL dlarfb( 'L', 'N', 'F', 'R', m-i+1, n, ib,
266 $ v( i, i ), ldv, t( 1, i ), ldt,
267 $ c( i, 1 ), ldc, work, ldwork )
268 END DO
269*
270 ELSE IF( right .AND. notran ) THEN
271*
272 kf = ((k-1)/mb)*mb+1
273 DO i = kf, 1, -mb
274 ib = min( mb, k-i+1 )
275 CALL dlarfb( 'R', 'T', 'F', 'R', m, n-i+1, ib,
276 $ v( i, i ), ldv, t( 1, i ), ldt,
277 $ c( 1, i ), ldc, work, ldwork )
278 END DO
279*
280 END IF
281*
282 RETURN
283*
284* End of DGEMLQT
285*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dlarfb(side, trans, direct, storev, m, n, k, v, ldv, t, ldt, c, ldc, work, ldwork)
DLARFB applies a block reflector or its transpose to a general rectangular matrix.
Definition dlarfb.f:195
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: