1ZLASR(1)            LAPACK auxiliary routine (version 3.1)            ZLASR(1)
2
3
4

NAME

6       ZLASR  - a sequence of real plane rotations to a complex matrix A, from
7       either the left or the right
8

SYNOPSIS

10       SUBROUTINE ZLASR( SIDE, PIVOT, DIRECT, M, N, C, S, A, LDA )
11
12           CHARACTER     DIRECT, PIVOT, SIDE
13
14           INTEGER       LDA, M, N
15
16           DOUBLE        PRECISION C( * ), S( * )
17
18           COMPLEX*16    A( LDA, * )
19

PURPOSE

21       ZLASR applies a sequence of real plane rotations to a complex matrix A,
22       from either the left or the right.
23
24       When SIDE = 'L', the transformation takes the form
25
26          A := P*A
27
28       and when SIDE = 'R', the transformation takes the form
29
30          A := A*P**T
31
32       where  P  is  an  orthogonal matrix consisting of a sequence of z plane
33       rotations, with z = M when SIDE = 'L' and z = N when SIDE  =  'R',  and
34       P**T is the transpose of P.
35
36       When DIRECT = 'F' (Forward sequence), then
37
38          P = P(z-1) * ... * P(2) * P(1)
39
40       and when DIRECT = 'B' (Backward sequence), then
41
42          P = P(1) * P(2) * ... * P(z-1)
43
44       where P(k) is a plane rotation matrix defined by the 2-by-2 rotation
45
46          R(k) = (  c(k)  s(k) )
47               = ( -s(k)  c(k) ).
48
49       When  PIVOT  =  'V' (Variable pivot), the rotation is performed for the
50       plane (k,k+1), i.e., P(k) has the form
51
52          P(k) = (  1                                            )
53                 (       ...                                     )
54                 (              1                                )
55                 (                   c(k)  s(k)                  )
56                 (                  -s(k)  c(k)                  )
57                 (                                1              )
58                 (                                     ...       )
59                 (                                            1  )
60
61       where R(k) appears as a rank-2 modification to the identity  matrix  in
62       rows and columns k and k+1.
63
64       When  PIVOT  = 'T' (Top pivot), the rotation is performed for the plane
65       (1,k+1), so P(k) has the form
66
67          P(k) = (  c(k)                    s(k)                 )
68                 (         1                                     )
69                 (              ...                              )
70                 (                     1                         )
71                 ( -s(k)                    c(k)                 )
72                 (                                 1             )
73                 (                                      ...      )
74                 (                                             1 )
75
76       where R(k) appears in rows and columns 1 and k+1.
77
78       Similarly, when PIVOT = 'B' (Bottom pivot), the rotation  is  performed
79       for the plane (k,z), giving P(k) the form
80
81          P(k) = ( 1                                             )
82                 (      ...                                      )
83                 (             1                                 )
84                 (                  c(k)                    s(k) )
85                 (                         1                     )
86                 (                              ...              )
87                 (                                     1         )
88                 (                 -s(k)                    c(k) )
89
90       where R(k) appears in rows and columns k and z.  The rotations are per‐
91       formed without ever forming P(k) explicitly.
92
93

ARGUMENTS

95       SIDE    (input) CHARACTER*1
96               Specifies whether the plane rotation matrix P is applied  to  A
97               on the left or the right.  = 'L':  Left, compute A := P*A
98               = 'R':  Right, compute A:= A*P**T
99
100       PIVOT   (input) CHARACTER*1
101               Specifies  the plane for which P(k) is a plane rotation matrix.
102               = 'V':  Variable pivot, the plane (k,k+1)
103               = 'T':  Top pivot, the plane (1,k+1)
104               = 'B':  Bottom pivot, the plane (k,z)
105
106       DIRECT  (input) CHARACTER*1
107               Specifies whether P is a forward or backward sequence of  plane
108               rotations.  = 'F':  Forward, P = P(z-1)*...*P(2)*P(1)
109               = 'B':  Backward, P = P(1)*P(2)*...*P(z-1)
110
111       M       (input) INTEGER
112               The  number  of  rows of the matrix A.  If m <= 1, an immediate
113               return is effected.
114
115       N       (input) INTEGER
116               The number of columns of the matrix A.  If n <= 1, an immediate
117               return is effected.
118
119       C       (input) DOUBLE PRECISION array, dimension
120               (M-1) if SIDE = 'L' (N-1) if SIDE = 'R' The cosines c(k) of the
121               plane rotations.
122
123       S       (input) DOUBLE PRECISION array, dimension
124               (M-1) if SIDE = 'L' (N-1) if SIDE = 'R' The sines s(k)  of  the
125               plane  rotations.  The 2-by-2 plane rotation part of the matrix
126               P(k), R(k), has the form R(k) = (  c(k)  s(k) ) (  -s(k)   c(k)
127               ).
128
129       A       (input/output) COMPLEX*16 array, dimension (LDA,N)
130               The  M-by-N matrix A.  On exit, A is overwritten by P*A if SIDE
131               = 'R' or by A*P**T if SIDE = 'L'.
132
133       LDA     (input) INTEGER
134               The leading dimension of the array A.  LDA >= max(1,M).
135
136
137
138 LAPACK auxiliary routine (versionNo3v.e1m)ber 2006                        ZLASR(1)
Impressum