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