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

◆ sopmtr()

subroutine sopmtr ( character side,
character uplo,
character trans,
integer m,
integer n,
real, dimension( * ) ap,
real, dimension( * ) tau,
real, dimension( ldc, * ) c,
integer ldc,
real, dimension( * ) work,
integer info )

SOPMTR

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

Purpose:
!>
!> SOPMTR 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 of order nq, with nq = m if
!> SIDE = 'L' and nq = n if SIDE = 'R'. Q is defined as the product of
!> nq-1 elementary reflectors, as returned by SSPTRD using packed
!> storage:
!>
!> if UPLO = 'U', Q = H(nq-1) . . . H(2) H(1);
!>
!> if UPLO = 'L', Q = H(1) H(2) . . . H(nq-1).
!> 
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]UPLO
!>          UPLO is CHARACTER*1
!>          = 'U': Upper triangular packed storage used in previous
!>                 call to SSPTRD;
!>          = 'L': Lower triangular packed storage used in previous
!>                 call to SSPTRD.
!> 
[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]AP
!>          AP is REAL array, dimension
!>                               (M*(M+1)/2) if SIDE = 'L'
!>                               (N*(N+1)/2) if SIDE = 'R'
!>          The vectors which define the elementary reflectors, as
!>          returned by SSPTRD.  AP is modified by the routine but
!>          restored on exit.
!> 
[in]TAU
!>          TAU is REAL array, dimension (M-1) if SIDE = 'L'
!>                                     or (N-1) if SIDE = 'R'
!>          TAU(i) must contain the scalar factor of the elementary
!>          reflector H(i), as returned by SSPTRD.
!> 
[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
!>                                   (N) if SIDE = 'L'
!>                                   (M) 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 146 of file sopmtr.f.

149*
150* -- LAPACK computational routine --
151* -- LAPACK is a software package provided by Univ. of Tennessee, --
152* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
153*
154* .. Scalar Arguments ..
155 CHARACTER SIDE, TRANS, UPLO
156 INTEGER INFO, LDC, M, N
157* ..
158* .. Array Arguments ..
159 REAL AP( * ), C( LDC, * ), TAU( * ), WORK( * )
160* ..
161*
162* =====================================================================
163*
164* .. Local Scalars ..
165 LOGICAL FORWRD, LEFT, NOTRAN, UPPER
166 INTEGER I, I1, I2, I3, IC, II, JC, MI, NI, NQ
167* ..
168* .. External Functions ..
169 LOGICAL LSAME
170 EXTERNAL lsame
171* ..
172* .. External Subroutines ..
173 EXTERNAL slarf1f, slarf1l, xerbla
174* ..
175* .. Intrinsic Functions ..
176 INTRINSIC max
177* ..
178* .. Executable Statements ..
179*
180* Test the input arguments
181*
182 info = 0
183 left = lsame( side, 'L' )
184 notran = lsame( trans, 'N' )
185 upper = lsame( uplo, 'U' )
186*
187* NQ is the order of Q
188*
189 IF( left ) THEN
190 nq = m
191 ELSE
192 nq = n
193 END IF
194 IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
195 info = -1
196 ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
197 info = -2
198 ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'T' ) ) THEN
199 info = -3
200 ELSE IF( m.LT.0 ) THEN
201 info = -4
202 ELSE IF( n.LT.0 ) THEN
203 info = -5
204 ELSE IF( ldc.LT.max( 1, m ) ) THEN
205 info = -9
206 END IF
207 IF( info.NE.0 ) THEN
208 CALL xerbla( 'SOPMTR', -info )
209 RETURN
210 END IF
211*
212* Quick return if possible
213*
214 IF( m.EQ.0 .OR. n.EQ.0 )
215 $ RETURN
216*
217 IF( upper ) THEN
218*
219* Q was determined by a call to SSPTRD with UPLO = 'U'
220*
221 forwrd = ( left .AND. notran ) .OR.
222 $ ( .NOT.left .AND. .NOT.notran )
223*
224 IF( forwrd ) THEN
225 i1 = 1
226 i2 = nq - 1
227 i3 = 1
228 ii = 2
229 ELSE
230 i1 = nq - 1
231 i2 = 1
232 i3 = -1
233 ii = nq*( nq+1 ) / 2 - 1
234 END IF
235*
236 IF( left ) THEN
237 ni = n
238 ELSE
239 mi = m
240 END IF
241*
242 DO 10 i = i1, i2, i3
243 IF( left ) THEN
244*
245* H(i) is applied to C(1:i,1:n)
246*
247 mi = i
248 ELSE
249*
250* H(i) is applied to C(1:m,1:i)
251*
252 ni = i
253 END IF
254*
255* Apply H(i)
256*
257 CALL slarf1l( side, mi, ni, ap( ii-i+1 ), 1, tau( i ), c,
258 $ ldc, work )
259*
260 IF( forwrd ) THEN
261 ii = ii + i + 2
262 ELSE
263 ii = ii - i - 1
264 END IF
265 10 CONTINUE
266 ELSE
267*
268* Q was determined by a call to SSPTRD with UPLO = 'L'.
269*
270 forwrd = ( left .AND. .NOT.notran ) .OR.
271 $ ( .NOT.left .AND. notran )
272*
273 IF( forwrd ) THEN
274 i1 = 1
275 i2 = nq - 1
276 i3 = 1
277 ii = 2
278 ELSE
279 i1 = nq - 1
280 i2 = 1
281 i3 = -1
282 ii = nq*( nq+1 ) / 2 - 1
283 END IF
284*
285 IF( left ) THEN
286 ni = n
287 jc = 1
288 ELSE
289 mi = m
290 ic = 1
291 END IF
292*
293 DO 20 i = i1, i2, i3
294 IF( left ) THEN
295*
296* H(i) is applied to C(i+1:m,1:n)
297*
298 mi = m - i
299 ic = i + 1
300 ELSE
301*
302* H(i) is applied to C(1:m,i+1:n)
303*
304 ni = n - i
305 jc = i + 1
306 END IF
307*
308* Apply H(i)
309*
310 CALL slarf1f( side, mi, ni, ap( ii ), 1, tau( i ),
311 $ c( ic, jc ), ldc, work )
312*
313 IF( forwrd ) THEN
314 ii = ii + nq - i + 1
315 ELSE
316 ii = ii - nq + i - 2
317 END IF
318 20 CONTINUE
319 END IF
320 RETURN
321*
322* End of SOPMTR
323*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine slarf1f(side, m, n, v, incv, tau, c, ldc, work)
SLARF1F applies an elementary reflector to a general rectangular
Definition slarf1f.f:123
subroutine slarf1l(side, m, n, v, incv, tau, c, ldc, work)
SLARF1L applies an elementary reflector to a general rectangular
Definition slarf1l.f:125
Here is the call graph for this function:
Here is the caller graph for this function: