LAPACK  3.9.0
LAPACK: Linear Algebra PACKage
sgemlqt.f
Go to the documentation of this file.
1 *> \brief \b SGEMLQT
2 *
3 * Definition:
4 * ===========
5 *
6 * SUBROUTINE SGEMLQT( SIDE, TRANS, M, N, K, MB, V, LDV, T, LDT,
7 * C, LDC, WORK, INFO )
8 *
9 * .. Scalar Arguments ..
10 * CHARACTER SIDE, TRANS
11 * INTEGER INFO, K, LDV, LDC, M, N, MB, LDT
12 * ..
13 * .. Array Arguments ..
14 * REAL V( LDV, * ), C( LDC, * ), T( LDT, * ), WORK( * )
15 * ..
16 *
17 *
18 *> \par Purpose:
19 * =============
20 *>
21 *> \verbatim
22 *>
23 *> DGEMLQT overwrites the general real M-by-N matrix C with
24 *>
25 *> SIDE = 'L' SIDE = 'R'
26 *> TRANS = 'N': Q C C Q
27 *> TRANS = 'T': Q**T C C Q**T
28 *>
29 *> where Q is a real orthogonal matrix defined as the product of K
30 *> elementary reflectors:
31 *>
32 *> Q = H(1) H(2) . . . H(K) = I - V T V**T
33 *>
34 *> generated using the compact WY representation as returned by DGELQT.
35 *>
36 *> Q is of order M if SIDE = 'L' and of order N if SIDE = 'R'.
37 *> \endverbatim
38 *
39 * Arguments:
40 * ==========
41 *
42 *> \param[in] SIDE
43 *> \verbatim
44 *> SIDE is CHARACTER*1
45 *> = 'L': apply Q or Q**T from the Left;
46 *> = 'R': apply Q or Q**T from the Right.
47 *> \endverbatim
48 *>
49 *> \param[in] TRANS
50 *> \verbatim
51 *> TRANS is CHARACTER*1
52 *> = 'N': No transpose, apply Q;
53 *> = 'C': Transpose, apply Q**T.
54 *> \endverbatim
55 *>
56 *> \param[in] M
57 *> \verbatim
58 *> M is INTEGER
59 *> The number of rows of the matrix C. M >= 0.
60 *> \endverbatim
61 *>
62 *> \param[in] N
63 *> \verbatim
64 *> N is INTEGER
65 *> The number of columns of the matrix C. N >= 0.
66 *> \endverbatim
67 *>
68 *> \param[in] K
69 *> \verbatim
70 *> K is INTEGER
71 *> The number of elementary reflectors whose product defines
72 *> the matrix Q.
73 *> If SIDE = 'L', M >= K >= 0;
74 *> if SIDE = 'R', N >= K >= 0.
75 *> \endverbatim
76 *>
77 *> \param[in] MB
78 *> \verbatim
79 *> MB is INTEGER
80 *> The block size used for the storage of T. K >= MB >= 1.
81 *> This must be the same value of MB used to generate T
82 *> in DGELQT.
83 *> \endverbatim
84 *>
85 *> \param[in] V
86 *> \verbatim
87 *> V is REAL array, dimension
88 *> (LDV,M) if SIDE = 'L',
89 *> (LDV,N) if SIDE = 'R'
90 *> The i-th row must contain the vector which defines the
91 *> elementary reflector H(i), for i = 1,2,...,k, as returned by
92 *> DGELQT in the first K rows of its array argument A.
93 *> \endverbatim
94 *>
95 *> \param[in] LDV
96 *> \verbatim
97 *> LDV is INTEGER
98 *> The leading dimension of the array V. LDV >= max(1,K).
99 *> \endverbatim
100 *>
101 *> \param[in] T
102 *> \verbatim
103 *> T is REAL array, dimension (LDT,K)
104 *> The upper triangular factors of the block reflectors
105 *> as returned by DGELQT, stored as a MB-by-K matrix.
106 *> \endverbatim
107 *>
108 *> \param[in] LDT
109 *> \verbatim
110 *> LDT is INTEGER
111 *> The leading dimension of the array T. LDT >= MB.
112 *> \endverbatim
113 *>
114 *> \param[in,out] C
115 *> \verbatim
116 *> C is REAL array, dimension (LDC,N)
117 *> On entry, the M-by-N matrix C.
118 *> On exit, C is overwritten by Q C, Q**T C, C Q**T or C Q.
119 *> \endverbatim
120 *>
121 *> \param[in] LDC
122 *> \verbatim
123 *> LDC is INTEGER
124 *> The leading dimension of the array C. LDC >= max(1,M).
125 *> \endverbatim
126 *>
127 *> \param[out] WORK
128 *> \verbatim
129 *> WORK is REAL array. The dimension of
130 *> WORK is N*MB if SIDE = 'L', or M*MB if SIDE = 'R'.
131 *> \endverbatim
132 *>
133 *> \param[out] INFO
134 *> \verbatim
135 *> INFO is INTEGER
136 *> = 0: successful exit
137 *> < 0: if INFO = -i, the i-th argument had an illegal value
138 *> \endverbatim
139 *
140 * Authors:
141 * ========
142 *
143 *> \author Univ. of Tennessee
144 *> \author Univ. of California Berkeley
145 *> \author Univ. of Colorado Denver
146 *> \author NAG Ltd.
147 *
148 *> \date November 2017
149 *
150 *> \ingroup doubleGEcomputational
151 *
152 * =====================================================================
153  SUBROUTINE sgemlqt( SIDE, TRANS, M, N, K, MB, V, LDV, T, LDT,
154  $ C, LDC, WORK, INFO )
155 *
156 * -- LAPACK computational routine (version 3.8.0) --
157 * -- LAPACK is a software package provided by Univ. of Tennessee, --
158 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
159 * November 2017
160 *
161 * .. Scalar Arguments ..
162  CHARACTER SIDE, TRANS
163  INTEGER INFO, K, LDV, LDC, M, N, MB, LDT
164 * ..
165 * .. Array Arguments ..
166  REAL V( LDV, * ), C( LDC, * ), T( LDT, * ), WORK( * )
167 * ..
168 *
169 * =====================================================================
170 *
171 * ..
172 * .. Local Scalars ..
173  LOGICAL LEFT, RIGHT, TRAN, NOTRAN
174  INTEGER I, IB, LDWORK, KF
175 * ..
176 * .. External Functions ..
177  LOGICAL LSAME
178  EXTERNAL lsame
179 * ..
180 * .. External Subroutines ..
181  EXTERNAL xerbla, slarfb
182 * ..
183 * .. Intrinsic Functions ..
184  INTRINSIC max, min
185 * ..
186 * .. Executable Statements ..
187 *
188 * .. Test the input arguments ..
189 *
190  info = 0
191  left = lsame( side, 'L' )
192  right = lsame( side, 'R' )
193  tran = lsame( trans, 'T' )
194  notran = lsame( trans, 'N' )
195 *
196  IF( left ) THEN
197  ldwork = max( 1, n )
198  ELSE IF ( right ) THEN
199  ldwork = max( 1, m )
200  END IF
201  IF( .NOT.left .AND. .NOT.right ) THEN
202  info = -1
203  ELSE IF( .NOT.tran .AND. .NOT.notran ) THEN
204  info = -2
205  ELSE IF( m.LT.0 ) THEN
206  info = -3
207  ELSE IF( n.LT.0 ) THEN
208  info = -4
209  ELSE IF( k.LT.0) THEN
210  info = -5
211  ELSE IF( mb.LT.1 .OR. (mb.GT.k .AND. k.GT.0)) THEN
212  info = -6
213  ELSE IF( ldv.LT.max( 1, k ) ) THEN
214  info = -8
215  ELSE IF( ldt.LT.mb ) THEN
216  info = -10
217  ELSE IF( ldc.LT.max( 1, m ) ) THEN
218  info = -12
219  END IF
220 *
221  IF( info.NE.0 ) THEN
222  CALL xerbla( 'SGEMLQT', -info )
223  RETURN
224  END IF
225 *
226 * .. Quick return if possible ..
227 *
228  IF( m.EQ.0 .OR. n.EQ.0 .OR. k.EQ.0 ) RETURN
229 *
230  IF( left .AND. notran ) THEN
231 *
232  DO i = 1, k, mb
233  ib = min( mb, k-i+1 )
234  CALL slarfb( 'L', 'T', 'F', 'R', m-i+1, n, ib,
235  $ v( i, i ), ldv, t( 1, i ), ldt,
236  $ c( i, 1 ), ldc, work, ldwork )
237  END DO
238 *
239  ELSE IF( right .AND. tran ) THEN
240 *
241  DO i = 1, k, mb
242  ib = min( mb, k-i+1 )
243  CALL slarfb( 'R', 'N', 'F', 'R', m, n-i+1, ib,
244  $ v( i, i ), ldv, t( 1, i ), ldt,
245  $ c( 1, i ), ldc, work, ldwork )
246  END DO
247 *
248  ELSE IF( left .AND. tran ) THEN
249 *
250  kf = ((k-1)/mb)*mb+1
251  DO i = kf, 1, -mb
252  ib = min( mb, k-i+1 )
253  CALL slarfb( 'L', 'N', 'F', 'R', m-i+1, n, ib,
254  $ v( i, i ), ldv, t( 1, i ), ldt,
255  $ c( i, 1 ), ldc, work, ldwork )
256  END DO
257 *
258  ELSE IF( right .AND. notran ) THEN
259 *
260  kf = ((k-1)/mb)*mb+1
261  DO i = kf, 1, -mb
262  ib = min( mb, k-i+1 )
263  CALL slarfb( 'R', 'T', 'F', 'R', m, n-i+1, ib,
264  $ v( i, i ), ldv, t( 1, i ), ldt,
265  $ c( 1, i ), ldc, work, ldwork )
266  END DO
267 *
268  END IF
269 *
270  RETURN
271 *
272 * End of SGEMLQT
273 *
274  END
slarfb
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:199
sgemlqt
subroutine sgemlqt(SIDE, TRANS, M, N, K, MB, V, LDV, T, LDT, C, LDC, WORK, INFO)
SGEMLQT
Definition: sgemlqt.f:155
xerbla
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62