LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dlasr.f
Go to the documentation of this file.
1*> \brief \b DLASR applies a sequence of plane rotations to a general rectangular matrix.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DLASR + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlasr.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlasr.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlasr.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DLASR( SIDE, PIVOT, DIRECT, M, N, C, S, A, LDA )
20*
21* .. Scalar Arguments ..
22* CHARACTER DIRECT, PIVOT, SIDE
23* INTEGER LDA, M, N
24* ..
25* .. Array Arguments ..
26* DOUBLE PRECISION A( LDA, * ), C( * ), S( * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> DLASR applies a sequence of plane rotations to a real matrix A,
36*> from either the left or the right.
37*>
38*> When SIDE = 'L', the transformation takes the form
39*>
40*> A := P*A
41*>
42*> and when SIDE = 'R', the transformation takes the form
43*>
44*> A := A*P**T
45*>
46*> where P is an orthogonal matrix consisting of a sequence of z plane
47*> rotations, with z = M when SIDE = 'L' and z = N when SIDE = 'R',
48*> and P**T is the transpose of P.
49*>
50*> When DIRECT = 'F' (Forward sequence), then
51*>
52*> P = P(z-1) * ... * P(2) * P(1)
53*>
54*> and when DIRECT = 'B' (Backward sequence), then
55*>
56*> P = P(1) * P(2) * ... * P(z-1)
57*>
58*> where P(k) is a plane rotation matrix defined by the 2-by-2 rotation
59*>
60*> R(k) = ( c(k) s(k) )
61*> = ( -s(k) c(k) ).
62*>
63*> When PIVOT = 'V' (Variable pivot), the rotation is performed
64*> for the plane (k,k+1), i.e., P(k) has the form
65*>
66*> P(k) = ( 1 )
67*> ( ... )
68*> ( 1 )
69*> ( c(k) s(k) )
70*> ( -s(k) c(k) )
71*> ( 1 )
72*> ( ... )
73*> ( 1 )
74*>
75*> where R(k) appears as a rank-2 modification to the identity matrix in
76*> rows and columns k and k+1.
77*>
78*> When PIVOT = 'T' (Top pivot), the rotation is performed for the
79*> plane (1,k+1), so P(k) has the form
80*>
81*> P(k) = ( c(k) s(k) )
82*> ( 1 )
83*> ( ... )
84*> ( 1 )
85*> ( -s(k) c(k) )
86*> ( 1 )
87*> ( ... )
88*> ( 1 )
89*>
90*> where R(k) appears in rows and columns 1 and k+1.
91*>
92*> Similarly, when PIVOT = 'B' (Bottom pivot), the rotation is
93*> performed for the plane (k,z), giving P(k) the form
94*>
95*> P(k) = ( 1 )
96*> ( ... )
97*> ( 1 )
98*> ( c(k) s(k) )
99*> ( 1 )
100*> ( ... )
101*> ( 1 )
102*> ( -s(k) c(k) )
103*>
104*> where R(k) appears in rows and columns k and z. The rotations are
105*> performed without ever forming P(k) explicitly.
106*> \endverbatim
107*
108* Arguments:
109* ==========
110*
111*> \param[in] SIDE
112*> \verbatim
113*> SIDE is CHARACTER*1
114*> Specifies whether the plane rotation matrix P is applied to
115*> A on the left or the right.
116*> = 'L': Left, compute A := P*A
117*> = 'R': Right, compute A:= A*P**T
118*> \endverbatim
119*>
120*> \param[in] PIVOT
121*> \verbatim
122*> PIVOT is CHARACTER*1
123*> Specifies the plane for which P(k) is a plane rotation
124*> matrix.
125*> = 'V': Variable pivot, the plane (k,k+1)
126*> = 'T': Top pivot, the plane (1,k+1)
127*> = 'B': Bottom pivot, the plane (k,z)
128*> \endverbatim
129*>
130*> \param[in] DIRECT
131*> \verbatim
132*> DIRECT is CHARACTER*1
133*> Specifies whether P is a forward or backward sequence of
134*> plane rotations.
135*> = 'F': Forward, P = P(z-1)*...*P(2)*P(1)
136*> = 'B': Backward, P = P(1)*P(2)*...*P(z-1)
137*> \endverbatim
138*>
139*> \param[in] M
140*> \verbatim
141*> M is INTEGER
142*> The number of rows of the matrix A. If m <= 1, an immediate
143*> return is effected.
144*> \endverbatim
145*>
146*> \param[in] N
147*> \verbatim
148*> N is INTEGER
149*> The number of columns of the matrix A. If n <= 1, an
150*> immediate return is effected.
151*> \endverbatim
152*>
153*> \param[in] C
154*> \verbatim
155*> C is DOUBLE PRECISION array, dimension
156*> (M-1) if SIDE = 'L'
157*> (N-1) if SIDE = 'R'
158*> The cosines c(k) of the plane rotations.
159*> \endverbatim
160*>
161*> \param[in] S
162*> \verbatim
163*> S is DOUBLE PRECISION array, dimension
164*> (M-1) if SIDE = 'L'
165*> (N-1) if SIDE = 'R'
166*> The sines s(k) of the plane rotations. The 2-by-2 plane
167*> rotation part of the matrix P(k), R(k), has the form
168*> R(k) = ( c(k) s(k) )
169*> ( -s(k) c(k) ).
170*> \endverbatim
171*>
172*> \param[in,out] A
173*> \verbatim
174*> A is DOUBLE PRECISION array, dimension (LDA,N)
175*> The M-by-N matrix A. On exit, A is overwritten by P*A if
176*> SIDE = 'L' or by A*P**T if SIDE = 'R'.
177*> \endverbatim
178*>
179*> \param[in] LDA
180*> \verbatim
181*> LDA is INTEGER
182*> The leading dimension of the array A. LDA >= max(1,M).
183*> \endverbatim
184*
185* Authors:
186* ========
187*
188*> \author Univ. of Tennessee
189*> \author Univ. of California Berkeley
190*> \author Univ. of Colorado Denver
191*> \author NAG Ltd.
192*
193*> \ingroup lasr
194*
195* =====================================================================
196 SUBROUTINE dlasr( SIDE, PIVOT, DIRECT, M, N, C, S, A, LDA )
197*
198* -- LAPACK auxiliary routine --
199* -- LAPACK is a software package provided by Univ. of Tennessee, --
200* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
201*
202* .. Scalar Arguments ..
203 CHARACTER DIRECT, PIVOT, SIDE
204 INTEGER LDA, M, N
205* ..
206* .. Array Arguments ..
207 DOUBLE PRECISION A( LDA, * ), C( * ), S( * )
208* ..
209*
210* =====================================================================
211*
212* .. Parameters ..
213 DOUBLE PRECISION ONE, ZERO
214 parameter( one = 1.0d+0, zero = 0.0d+0 )
215* ..
216* .. Local Scalars ..
217 INTEGER I, INFO, J
218 DOUBLE PRECISION CTEMP, STEMP, TEMP
219* ..
220* .. External Functions ..
221 LOGICAL LSAME
222 EXTERNAL lsame
223* ..
224* .. External Subroutines ..
225 EXTERNAL xerbla
226* ..
227* .. Intrinsic Functions ..
228 INTRINSIC max
229* ..
230* .. Executable Statements ..
231*
232* Test the input parameters
233*
234 info = 0
235 IF( .NOT.( lsame( side, 'L' ) .OR.
236 $ lsame( side, 'R' ) ) ) THEN
237 info = 1
238 ELSE IF( .NOT.( lsame( pivot, 'V' ) .OR. lsame( pivot,
239 $ 'T' ) .OR. lsame( pivot, 'B' ) ) ) THEN
240 info = 2
241 ELSE IF( .NOT.( lsame( direct, 'F' ) .OR.
242 $ lsame( direct, 'B' ) ) )
243 $ THEN
244 info = 3
245 ELSE IF( m.LT.0 ) THEN
246 info = 4
247 ELSE IF( n.LT.0 ) THEN
248 info = 5
249 ELSE IF( lda.LT.max( 1, m ) ) THEN
250 info = 9
251 END IF
252 IF( info.NE.0 ) THEN
253 CALL xerbla( 'DLASR ', info )
254 RETURN
255 END IF
256*
257* Quick return if possible
258*
259 IF( ( m.EQ.0 ) .OR. ( n.EQ.0 ) )
260 $ RETURN
261 IF( lsame( side, 'L' ) ) THEN
262*
263* Form P * A
264*
265 IF( lsame( pivot, 'V' ) ) THEN
266 IF( lsame( direct, 'F' ) ) THEN
267 DO 20 j = 1, m - 1
268 ctemp = c( j )
269 stemp = s( j )
270 IF( ( ctemp.NE.one ) .OR. ( stemp.NE.zero ) ) THEN
271 DO 10 i = 1, n
272 temp = a( j+1, i )
273 a( j+1, i ) = ctemp*temp - stemp*a( j, i )
274 a( j, i ) = stemp*temp + ctemp*a( j, i )
275 10 CONTINUE
276 END IF
277 20 CONTINUE
278 ELSE IF( lsame( direct, 'B' ) ) THEN
279 DO 40 j = m - 1, 1, -1
280 ctemp = c( j )
281 stemp = s( j )
282 IF( ( ctemp.NE.one ) .OR. ( stemp.NE.zero ) ) THEN
283 DO 30 i = 1, n
284 temp = a( j+1, i )
285 a( j+1, i ) = ctemp*temp - stemp*a( j, i )
286 a( j, i ) = stemp*temp + ctemp*a( j, i )
287 30 CONTINUE
288 END IF
289 40 CONTINUE
290 END IF
291 ELSE IF( lsame( pivot, 'T' ) ) THEN
292 IF( lsame( direct, 'F' ) ) THEN
293 DO 60 j = 2, m
294 ctemp = c( j-1 )
295 stemp = s( j-1 )
296 IF( ( ctemp.NE.one ) .OR. ( stemp.NE.zero ) ) THEN
297 DO 50 i = 1, n
298 temp = a( j, i )
299 a( j, i ) = ctemp*temp - stemp*a( 1, i )
300 a( 1, i ) = stemp*temp + ctemp*a( 1, i )
301 50 CONTINUE
302 END IF
303 60 CONTINUE
304 ELSE IF( lsame( direct, 'B' ) ) THEN
305 DO 80 j = m, 2, -1
306 ctemp = c( j-1 )
307 stemp = s( j-1 )
308 IF( ( ctemp.NE.one ) .OR. ( stemp.NE.zero ) ) THEN
309 DO 70 i = 1, n
310 temp = a( j, i )
311 a( j, i ) = ctemp*temp - stemp*a( 1, i )
312 a( 1, i ) = stemp*temp + ctemp*a( 1, i )
313 70 CONTINUE
314 END IF
315 80 CONTINUE
316 END IF
317 ELSE IF( lsame( pivot, 'B' ) ) THEN
318 IF( lsame( direct, 'F' ) ) THEN
319 DO 100 j = 1, m - 1
320 ctemp = c( j )
321 stemp = s( j )
322 IF( ( ctemp.NE.one ) .OR. ( stemp.NE.zero ) ) THEN
323 DO 90 i = 1, n
324 temp = a( j, i )
325 a( j, i ) = stemp*a( m, i ) + ctemp*temp
326 a( m, i ) = ctemp*a( m, i ) - stemp*temp
327 90 CONTINUE
328 END IF
329 100 CONTINUE
330 ELSE IF( lsame( direct, 'B' ) ) THEN
331 DO 120 j = m - 1, 1, -1
332 ctemp = c( j )
333 stemp = s( j )
334 IF( ( ctemp.NE.one ) .OR. ( stemp.NE.zero ) ) THEN
335 DO 110 i = 1, n
336 temp = a( j, i )
337 a( j, i ) = stemp*a( m, i ) + ctemp*temp
338 a( m, i ) = ctemp*a( m, i ) - stemp*temp
339 110 CONTINUE
340 END IF
341 120 CONTINUE
342 END IF
343 END IF
344 ELSE IF( lsame( side, 'R' ) ) THEN
345*
346* Form A * P**T
347*
348 IF( lsame( pivot, 'V' ) ) THEN
349 IF( lsame( direct, 'F' ) ) THEN
350 DO 140 j = 1, n - 1
351 ctemp = c( j )
352 stemp = s( j )
353 IF( ( ctemp.NE.one ) .OR. ( stemp.NE.zero ) ) THEN
354 DO 130 i = 1, m
355 temp = a( i, j+1 )
356 a( i, j+1 ) = ctemp*temp - stemp*a( i, j )
357 a( i, j ) = stemp*temp + ctemp*a( i, j )
358 130 CONTINUE
359 END IF
360 140 CONTINUE
361 ELSE IF( lsame( direct, 'B' ) ) THEN
362 DO 160 j = n - 1, 1, -1
363 ctemp = c( j )
364 stemp = s( j )
365 IF( ( ctemp.NE.one ) .OR. ( stemp.NE.zero ) ) THEN
366 DO 150 i = 1, m
367 temp = a( i, j+1 )
368 a( i, j+1 ) = ctemp*temp - stemp*a( i, j )
369 a( i, j ) = stemp*temp + ctemp*a( i, j )
370 150 CONTINUE
371 END IF
372 160 CONTINUE
373 END IF
374 ELSE IF( lsame( pivot, 'T' ) ) THEN
375 IF( lsame( direct, 'F' ) ) THEN
376 DO 180 j = 2, n
377 ctemp = c( j-1 )
378 stemp = s( j-1 )
379 IF( ( ctemp.NE.one ) .OR. ( stemp.NE.zero ) ) THEN
380 DO 170 i = 1, m
381 temp = a( i, j )
382 a( i, j ) = ctemp*temp - stemp*a( i, 1 )
383 a( i, 1 ) = stemp*temp + ctemp*a( i, 1 )
384 170 CONTINUE
385 END IF
386 180 CONTINUE
387 ELSE IF( lsame( direct, 'B' ) ) THEN
388 DO 200 j = n, 2, -1
389 ctemp = c( j-1 )
390 stemp = s( j-1 )
391 IF( ( ctemp.NE.one ) .OR. ( stemp.NE.zero ) ) THEN
392 DO 190 i = 1, m
393 temp = a( i, j )
394 a( i, j ) = ctemp*temp - stemp*a( i, 1 )
395 a( i, 1 ) = stemp*temp + ctemp*a( i, 1 )
396 190 CONTINUE
397 END IF
398 200 CONTINUE
399 END IF
400 ELSE IF( lsame( pivot, 'B' ) ) THEN
401 IF( lsame( direct, 'F' ) ) THEN
402 DO 220 j = 1, n - 1
403 ctemp = c( j )
404 stemp = s( j )
405 IF( ( ctemp.NE.one ) .OR. ( stemp.NE.zero ) ) THEN
406 DO 210 i = 1, m
407 temp = a( i, j )
408 a( i, j ) = stemp*a( i, n ) + ctemp*temp
409 a( i, n ) = ctemp*a( i, n ) - stemp*temp
410 210 CONTINUE
411 END IF
412 220 CONTINUE
413 ELSE IF( lsame( direct, 'B' ) ) THEN
414 DO 240 j = n - 1, 1, -1
415 ctemp = c( j )
416 stemp = s( j )
417 IF( ( ctemp.NE.one ) .OR. ( stemp.NE.zero ) ) THEN
418 DO 230 i = 1, m
419 temp = a( i, j )
420 a( i, j ) = stemp*a( i, n ) + ctemp*temp
421 a( i, n ) = ctemp*a( i, n ) - stemp*temp
422 230 CONTINUE
423 END IF
424 240 CONTINUE
425 END IF
426 END IF
427 END IF
428*
429 RETURN
430*
431* End of DLASR
432*
433 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dlasr(side, pivot, direct, m, n, c, s, a, lda)
DLASR applies a sequence of plane rotations to a general rectangular matrix.
Definition dlasr.f:197