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