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