comparison libcruft/lapack/zlasr.f @ 7034:68db500cb558

[project @ 2007-10-16 18:54:19 by jwe]
author jwe
date Tue, 16 Oct 2007 18:54:23 +0000
parents 15cddaacbc2d
children
comparison
equal deleted inserted replaced
7033:f0142f2afdc6 7034:68db500cb558
1 SUBROUTINE ZLASR( SIDE, PIVOT, DIRECT, M, N, C, S, A, LDA ) 1 SUBROUTINE ZLASR( SIDE, PIVOT, DIRECT, M, N, C, S, A, LDA )
2 * 2 *
3 * -- LAPACK auxiliary routine (version 3.0) -- 3 * -- LAPACK auxiliary routine (version 3.1) --
4 * Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd., 4 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
5 * Courant Institute, Argonne National Lab, and Rice University 5 * November 2006
6 * October 31, 1992
7 * 6 *
8 * .. Scalar Arguments .. 7 * .. Scalar Arguments ..
9 CHARACTER DIRECT, PIVOT, SIDE 8 CHARACTER DIRECT, PIVOT, SIDE
10 INTEGER LDA, M, N 9 INTEGER LDA, M, N
11 * .. 10 * ..
15 * .. 14 * ..
16 * 15 *
17 * Purpose 16 * Purpose
18 * ======= 17 * =======
19 * 18 *
20 * ZLASR performs the transformation 19 * ZLASR applies a sequence of real plane rotations to a complex matrix
21 * 20 * A, from either the left or the right.
22 * A := P*A, when SIDE = 'L' or 'l' ( Left-hand side ) 21 *
23 * 22 * When SIDE = 'L', the transformation takes the form
24 * A := A*P', when SIDE = 'R' or 'r' ( Right-hand side ) 23 *
25 * 24 * A := P*A
26 * where A is an m by n complex matrix and P is an orthogonal matrix, 25 *
27 * consisting of a sequence of plane rotations determined by the 26 * and when SIDE = 'R', the transformation takes the form
28 * parameters PIVOT and DIRECT as follows ( z = m when SIDE = 'L' or 'l' 27 *
29 * and z = n when SIDE = 'R' or 'r' ): 28 * A := A*P**T
30 * 29 *
31 * When DIRECT = 'F' or 'f' ( Forward sequence ) then 30 * where P is an orthogonal matrix consisting of a sequence of z plane
32 * 31 * rotations, with z = M when SIDE = 'L' and z = N when SIDE = 'R',
33 * P = P( z - 1 )*...*P( 2 )*P( 1 ), 32 * and P**T is the transpose of P.
34 * 33 *
35 * and when DIRECT = 'B' or 'b' ( Backward sequence ) then 34 * When DIRECT = 'F' (Forward sequence), then
36 * 35 *
37 * P = P( 1 )*P( 2 )*...*P( z - 1 ), 36 * P = P(z-1) * ... * P(2) * P(1)
38 * 37 *
39 * where P( k ) is a plane rotation matrix for the following planes: 38 * and when DIRECT = 'B' (Backward sequence), then
40 * 39 *
41 * when PIVOT = 'V' or 'v' ( Variable pivot ), 40 * P = P(1) * P(2) * ... * P(z-1)
42 * the plane ( k, k + 1 ) 41 *
43 * 42 * where P(k) is a plane rotation matrix defined by the 2-by-2 rotation
44 * when PIVOT = 'T' or 't' ( Top pivot ), 43 *
45 * the plane ( 1, k + 1 ) 44 * R(k) = ( c(k) s(k) )
46 * 45 * = ( -s(k) c(k) ).
47 * when PIVOT = 'B' or 'b' ( Bottom pivot ), 46 *
48 * the plane ( k, z ) 47 * When PIVOT = 'V' (Variable pivot), the rotation is performed
49 * 48 * for the plane (k,k+1), i.e., P(k) has the form
50 * c( k ) and s( k ) must contain the cosine and sine that define the 49 *
51 * matrix P( k ). The two by two plane rotation part of the matrix 50 * P(k) = ( 1 )
52 * P( k ), R( k ), is assumed to be of the form 51 * ( ... )
53 * 52 * ( 1 )
54 * R( k ) = ( c( k ) s( k ) ). 53 * ( c(k) s(k) )
55 * ( -s( k ) c( k ) ) 54 * ( -s(k) c(k) )
55 * ( 1 )
56 * ( ... )
57 * ( 1 )
58 *
59 * where R(k) appears as a rank-2 modification to the identity matrix in
60 * rows and columns k and k+1.
61 *
62 * When PIVOT = 'T' (Top pivot), the rotation is performed for the
63 * plane (1,k+1), so P(k) has the form
64 *
65 * P(k) = ( c(k) s(k) )
66 * ( 1 )
67 * ( ... )
68 * ( 1 )
69 * ( -s(k) c(k) )
70 * ( 1 )
71 * ( ... )
72 * ( 1 )
73 *
74 * where R(k) appears in rows and columns 1 and k+1.
75 *
76 * Similarly, when PIVOT = 'B' (Bottom pivot), the rotation is
77 * performed for the plane (k,z), giving P(k) the form
78 *
79 * P(k) = ( 1 )
80 * ( ... )
81 * ( 1 )
82 * ( c(k) s(k) )
83 * ( 1 )
84 * ( ... )
85 * ( 1 )
86 * ( -s(k) c(k) )
87 *
88 * where R(k) appears in rows and columns k and z. The rotations are
89 * performed without ever forming P(k) explicitly.
56 * 90 *
57 * Arguments 91 * Arguments
58 * ========= 92 * =========
59 * 93 *
60 * SIDE (input) CHARACTER*1 94 * SIDE (input) CHARACTER*1
61 * Specifies whether the plane rotation matrix P is applied to 95 * Specifies whether the plane rotation matrix P is applied to
62 * A on the left or the right. 96 * A on the left or the right.
63 * = 'L': Left, compute A := P*A 97 * = 'L': Left, compute A := P*A
64 * = 'R': Right, compute A:= A*P' 98 * = 'R': Right, compute A:= A*P**T
65 *
66 * DIRECT (input) CHARACTER*1
67 * Specifies whether P is a forward or backward sequence of
68 * plane rotations.
69 * = 'F': Forward, P = P( z - 1 )*...*P( 2 )*P( 1 )
70 * = 'B': Backward, P = P( 1 )*P( 2 )*...*P( z - 1 )
71 * 99 *
72 * PIVOT (input) CHARACTER*1 100 * PIVOT (input) CHARACTER*1
73 * Specifies the plane for which P(k) is a plane rotation 101 * Specifies the plane for which P(k) is a plane rotation
74 * matrix. 102 * matrix.
75 * = 'V': Variable pivot, the plane (k,k+1) 103 * = 'V': Variable pivot, the plane (k,k+1)
76 * = 'T': Top pivot, the plane (1,k+1) 104 * = 'T': Top pivot, the plane (1,k+1)
77 * = 'B': Bottom pivot, the plane (k,z) 105 * = 'B': Bottom pivot, the plane (k,z)
78 * 106 *
107 * DIRECT (input) CHARACTER*1
108 * Specifies whether P is a forward or backward sequence of
109 * plane rotations.
110 * = 'F': Forward, P = P(z-1)*...*P(2)*P(1)
111 * = 'B': Backward, P = P(1)*P(2)*...*P(z-1)
112 *
79 * M (input) INTEGER 113 * M (input) INTEGER
80 * The number of rows of the matrix A. If m <= 1, an immediate 114 * The number of rows of the matrix A. If m <= 1, an immediate
81 * return is effected. 115 * return is effected.
82 * 116 *
83 * N (input) INTEGER 117 * N (input) INTEGER
84 * The number of columns of the matrix A. If n <= 1, an 118 * The number of columns of the matrix A. If n <= 1, an
85 * immediate return is effected. 119 * immediate return is effected.
86 * 120 *
87 * C, S (input) DOUBLE PRECISION arrays, dimension 121 * C (input) DOUBLE PRECISION array, dimension
88 * (M-1) if SIDE = 'L' 122 * (M-1) if SIDE = 'L'
89 * (N-1) if SIDE = 'R' 123 * (N-1) if SIDE = 'R'
90 * c(k) and s(k) contain the cosine and sine that define the 124 * The cosines c(k) of the plane rotations.
91 * matrix P(k). The two by two plane rotation part of the 125 *
92 * matrix P(k), R(k), is assumed to be of the form 126 * S (input) DOUBLE PRECISION array, dimension
93 * R( k ) = ( c( k ) s( k ) ). 127 * (M-1) if SIDE = 'L'
94 * ( -s( k ) c( k ) ) 128 * (N-1) if SIDE = 'R'
129 * The sines s(k) of the plane rotations. The 2-by-2 plane
130 * rotation part of the matrix P(k), R(k), has the form
131 * R(k) = ( c(k) s(k) )
132 * ( -s(k) c(k) ).
95 * 133 *
96 * A (input/output) COMPLEX*16 array, dimension (LDA,N) 134 * A (input/output) COMPLEX*16 array, dimension (LDA,N)
97 * The m by n matrix A. On exit, A is overwritten by P*A if 135 * The M-by-N matrix A. On exit, A is overwritten by P*A if
98 * SIDE = 'R' or by A*P' if SIDE = 'L'. 136 * SIDE = 'R' or by A*P**T if SIDE = 'L'.
99 * 137 *
100 * LDA (input) INTEGER 138 * LDA (input) INTEGER
101 * The leading dimension of the array A. LDA >= max(1,M). 139 * The leading dimension of the array A. LDA >= max(1,M).
102 * 140 *
103 * ===================================================================== 141 * =====================================================================