root / src / lapack / double / dlarft.f @ 10
Historique | Voir | Annoter | Télécharger (8,3 ko)
1 | 1 | pfleura2 | SUBROUTINE DLARFT( DIRECT, STOREV, N, K, V, LDV, TAU, T, LDT ) |
---|---|---|---|
2 | 1 | pfleura2 | IMPLICIT NONE |
3 | 1 | pfleura2 | * |
4 | 1 | pfleura2 | * -- LAPACK auxiliary routine (version 3.2) -- |
5 | 1 | pfleura2 | * -- LAPACK is a software package provided by Univ. of Tennessee, -- |
6 | 1 | pfleura2 | * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..-- |
7 | 1 | pfleura2 | * November 2006 |
8 | 1 | pfleura2 | * |
9 | 1 | pfleura2 | * .. Scalar Arguments .. |
10 | 1 | pfleura2 | CHARACTER DIRECT, STOREV |
11 | 1 | pfleura2 | INTEGER K, LDT, LDV, N |
12 | 1 | pfleura2 | * .. |
13 | 1 | pfleura2 | * .. Array Arguments .. |
14 | 1 | pfleura2 | DOUBLE PRECISION T( LDT, * ), TAU( * ), V( LDV, * ) |
15 | 1 | pfleura2 | * .. |
16 | 1 | pfleura2 | * |
17 | 1 | pfleura2 | * Purpose |
18 | 1 | pfleura2 | * ======= |
19 | 1 | pfleura2 | * |
20 | 1 | pfleura2 | * DLARFT forms the triangular factor T of a real block reflector H |
21 | 1 | pfleura2 | * of order n, which is defined as a product of k elementary reflectors. |
22 | 1 | pfleura2 | * |
23 | 1 | pfleura2 | * If DIRECT = 'F', H = H(1) H(2) . . . H(k) and T is upper triangular; |
24 | 1 | pfleura2 | * |
25 | 1 | pfleura2 | * If DIRECT = 'B', H = H(k) . . . H(2) H(1) and T is lower triangular. |
26 | 1 | pfleura2 | * |
27 | 1 | pfleura2 | * If STOREV = 'C', the vector which defines the elementary reflector |
28 | 1 | pfleura2 | * H(i) is stored in the i-th column of the array V, and |
29 | 1 | pfleura2 | * |
30 | 1 | pfleura2 | * H = I - V * T * V' |
31 | 1 | pfleura2 | * |
32 | 1 | pfleura2 | * If STOREV = 'R', the vector which defines the elementary reflector |
33 | 1 | pfleura2 | * H(i) is stored in the i-th row of the array V, and |
34 | 1 | pfleura2 | * |
35 | 1 | pfleura2 | * H = I - V' * T * V |
36 | 1 | pfleura2 | * |
37 | 1 | pfleura2 | * Arguments |
38 | 1 | pfleura2 | * ========= |
39 | 1 | pfleura2 | * |
40 | 1 | pfleura2 | * DIRECT (input) CHARACTER*1 |
41 | 1 | pfleura2 | * Specifies the order in which the elementary reflectors are |
42 | 1 | pfleura2 | * multiplied to form the block reflector: |
43 | 1 | pfleura2 | * = 'F': H = H(1) H(2) . . . H(k) (Forward) |
44 | 1 | pfleura2 | * = 'B': H = H(k) . . . H(2) H(1) (Backward) |
45 | 1 | pfleura2 | * |
46 | 1 | pfleura2 | * STOREV (input) CHARACTER*1 |
47 | 1 | pfleura2 | * Specifies how the vectors which define the elementary |
48 | 1 | pfleura2 | * reflectors are stored (see also Further Details): |
49 | 1 | pfleura2 | * = 'C': columnwise |
50 | 1 | pfleura2 | * = 'R': rowwise |
51 | 1 | pfleura2 | * |
52 | 1 | pfleura2 | * N (input) INTEGER |
53 | 1 | pfleura2 | * The order of the block reflector H. N >= 0. |
54 | 1 | pfleura2 | * |
55 | 1 | pfleura2 | * K (input) INTEGER |
56 | 1 | pfleura2 | * The order of the triangular factor T (= the number of |
57 | 1 | pfleura2 | * elementary reflectors). K >= 1. |
58 | 1 | pfleura2 | * |
59 | 1 | pfleura2 | * V (input/output) DOUBLE PRECISION array, dimension |
60 | 1 | pfleura2 | * (LDV,K) if STOREV = 'C' |
61 | 1 | pfleura2 | * (LDV,N) if STOREV = 'R' |
62 | 1 | pfleura2 | * The matrix V. See further details. |
63 | 1 | pfleura2 | * |
64 | 1 | pfleura2 | * LDV (input) INTEGER |
65 | 1 | pfleura2 | * The leading dimension of the array V. |
66 | 1 | pfleura2 | * If STOREV = 'C', LDV >= max(1,N); if STOREV = 'R', LDV >= K. |
67 | 1 | pfleura2 | * |
68 | 1 | pfleura2 | * TAU (input) DOUBLE PRECISION array, dimension (K) |
69 | 1 | pfleura2 | * TAU(i) must contain the scalar factor of the elementary |
70 | 1 | pfleura2 | * reflector H(i). |
71 | 1 | pfleura2 | * |
72 | 1 | pfleura2 | * T (output) DOUBLE PRECISION array, dimension (LDT,K) |
73 | 1 | pfleura2 | * The k by k triangular factor T of the block reflector. |
74 | 1 | pfleura2 | * If DIRECT = 'F', T is upper triangular; if DIRECT = 'B', T is |
75 | 1 | pfleura2 | * lower triangular. The rest of the array is not used. |
76 | 1 | pfleura2 | * |
77 | 1 | pfleura2 | * LDT (input) INTEGER |
78 | 1 | pfleura2 | * The leading dimension of the array T. LDT >= K. |
79 | 1 | pfleura2 | * |
80 | 1 | pfleura2 | * Further Details |
81 | 1 | pfleura2 | * =============== |
82 | 1 | pfleura2 | * |
83 | 1 | pfleura2 | * The shape of the matrix V and the storage of the vectors which define |
84 | 1 | pfleura2 | * the H(i) is best illustrated by the following example with n = 5 and |
85 | 1 | pfleura2 | * k = 3. The elements equal to 1 are not stored; the corresponding |
86 | 1 | pfleura2 | * array elements are modified but restored on exit. The rest of the |
87 | 1 | pfleura2 | * array is not used. |
88 | 1 | pfleura2 | * |
89 | 1 | pfleura2 | * DIRECT = 'F' and STOREV = 'C': DIRECT = 'F' and STOREV = 'R': |
90 | 1 | pfleura2 | * |
91 | 1 | pfleura2 | * V = ( 1 ) V = ( 1 v1 v1 v1 v1 ) |
92 | 1 | pfleura2 | * ( v1 1 ) ( 1 v2 v2 v2 ) |
93 | 1 | pfleura2 | * ( v1 v2 1 ) ( 1 v3 v3 ) |
94 | 1 | pfleura2 | * ( v1 v2 v3 ) |
95 | 1 | pfleura2 | * ( v1 v2 v3 ) |
96 | 1 | pfleura2 | * |
97 | 1 | pfleura2 | * DIRECT = 'B' and STOREV = 'C': DIRECT = 'B' and STOREV = 'R': |
98 | 1 | pfleura2 | * |
99 | 1 | pfleura2 | * V = ( v1 v2 v3 ) V = ( v1 v1 1 ) |
100 | 1 | pfleura2 | * ( v1 v2 v3 ) ( v2 v2 v2 1 ) |
101 | 1 | pfleura2 | * ( 1 v2 v3 ) ( v3 v3 v3 v3 1 ) |
102 | 1 | pfleura2 | * ( 1 v3 ) |
103 | 1 | pfleura2 | * ( 1 ) |
104 | 1 | pfleura2 | * |
105 | 1 | pfleura2 | * ===================================================================== |
106 | 1 | pfleura2 | * |
107 | 1 | pfleura2 | * .. Parameters .. |
108 | 1 | pfleura2 | DOUBLE PRECISION ONE, ZERO |
109 | 1 | pfleura2 | PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 ) |
110 | 1 | pfleura2 | * .. |
111 | 1 | pfleura2 | * .. Local Scalars .. |
112 | 1 | pfleura2 | INTEGER I, J, PREVLASTV, LASTV |
113 | 1 | pfleura2 | DOUBLE PRECISION VII |
114 | 1 | pfleura2 | * .. |
115 | 1 | pfleura2 | * .. External Subroutines .. |
116 | 1 | pfleura2 | EXTERNAL DGEMV, DTRMV |
117 | 1 | pfleura2 | * .. |
118 | 1 | pfleura2 | * .. External Functions .. |
119 | 1 | pfleura2 | LOGICAL LSAME |
120 | 1 | pfleura2 | EXTERNAL LSAME |
121 | 1 | pfleura2 | * .. |
122 | 1 | pfleura2 | * .. Executable Statements .. |
123 | 1 | pfleura2 | * |
124 | 1 | pfleura2 | * Quick return if possible |
125 | 1 | pfleura2 | * |
126 | 1 | pfleura2 | IF( N.EQ.0 ) |
127 | 1 | pfleura2 | $ RETURN |
128 | 1 | pfleura2 | * |
129 | 1 | pfleura2 | IF( LSAME( DIRECT, 'F' ) ) THEN |
130 | 1 | pfleura2 | PREVLASTV = N |
131 | 1 | pfleura2 | DO 20 I = 1, K |
132 | 1 | pfleura2 | PREVLASTV = MAX( I, PREVLASTV ) |
133 | 1 | pfleura2 | IF( TAU( I ).EQ.ZERO ) THEN |
134 | 1 | pfleura2 | * |
135 | 1 | pfleura2 | * H(i) = I |
136 | 1 | pfleura2 | * |
137 | 1 | pfleura2 | DO 10 J = 1, I |
138 | 1 | pfleura2 | T( J, I ) = ZERO |
139 | 1 | pfleura2 | 10 CONTINUE |
140 | 1 | pfleura2 | ELSE |
141 | 1 | pfleura2 | * |
142 | 1 | pfleura2 | * general case |
143 | 1 | pfleura2 | * |
144 | 1 | pfleura2 | VII = V( I, I ) |
145 | 1 | pfleura2 | V( I, I ) = ONE |
146 | 1 | pfleura2 | IF( LSAME( STOREV, 'C' ) ) THEN |
147 | 1 | pfleura2 | ! Skip any trailing zeros. |
148 | 1 | pfleura2 | DO LASTV = N, I+1, -1 |
149 | 1 | pfleura2 | IF( V( LASTV, I ).NE.ZERO ) EXIT |
150 | 1 | pfleura2 | END DO |
151 | 1 | pfleura2 | J = MIN( LASTV, PREVLASTV ) |
152 | 1 | pfleura2 | * |
153 | 1 | pfleura2 | * T(1:i-1,i) := - tau(i) * V(i:j,1:i-1)' * V(i:j,i) |
154 | 1 | pfleura2 | * |
155 | 1 | pfleura2 | CALL DGEMV( 'Transpose', J-I+1, I-1, -TAU( I ), |
156 | 1 | pfleura2 | $ V( I, 1 ), LDV, V( I, I ), 1, ZERO, |
157 | 1 | pfleura2 | $ T( 1, I ), 1 ) |
158 | 1 | pfleura2 | ELSE |
159 | 1 | pfleura2 | ! Skip any trailing zeros. |
160 | 1 | pfleura2 | DO LASTV = N, I+1, -1 |
161 | 1 | pfleura2 | IF( V( I, LASTV ).NE.ZERO ) EXIT |
162 | 1 | pfleura2 | END DO |
163 | 1 | pfleura2 | J = MIN( LASTV, PREVLASTV ) |
164 | 1 | pfleura2 | * |
165 | 1 | pfleura2 | * T(1:i-1,i) := - tau(i) * V(1:i-1,i:j) * V(i,i:j)' |
166 | 1 | pfleura2 | * |
167 | 1 | pfleura2 | CALL DGEMV( 'No transpose', I-1, J-I+1, -TAU( I ), |
168 | 1 | pfleura2 | $ V( 1, I ), LDV, V( I, I ), LDV, ZERO, |
169 | 1 | pfleura2 | $ T( 1, I ), 1 ) |
170 | 1 | pfleura2 | END IF |
171 | 1 | pfleura2 | V( I, I ) = VII |
172 | 1 | pfleura2 | * |
173 | 1 | pfleura2 | * T(1:i-1,i) := T(1:i-1,1:i-1) * T(1:i-1,i) |
174 | 1 | pfleura2 | * |
175 | 1 | pfleura2 | CALL DTRMV( 'Upper', 'No transpose', 'Non-unit', I-1, T, |
176 | 1 | pfleura2 | $ LDT, T( 1, I ), 1 ) |
177 | 1 | pfleura2 | T( I, I ) = TAU( I ) |
178 | 1 | pfleura2 | IF( I.GT.1 ) THEN |
179 | 1 | pfleura2 | PREVLASTV = MAX( PREVLASTV, LASTV ) |
180 | 1 | pfleura2 | ELSE |
181 | 1 | pfleura2 | PREVLASTV = LASTV |
182 | 1 | pfleura2 | END IF |
183 | 1 | pfleura2 | END IF |
184 | 1 | pfleura2 | 20 CONTINUE |
185 | 1 | pfleura2 | ELSE |
186 | 1 | pfleura2 | PREVLASTV = 1 |
187 | 1 | pfleura2 | DO 40 I = K, 1, -1 |
188 | 1 | pfleura2 | IF( TAU( I ).EQ.ZERO ) THEN |
189 | 1 | pfleura2 | * |
190 | 1 | pfleura2 | * H(i) = I |
191 | 1 | pfleura2 | * |
192 | 1 | pfleura2 | DO 30 J = I, K |
193 | 1 | pfleura2 | T( J, I ) = ZERO |
194 | 1 | pfleura2 | 30 CONTINUE |
195 | 1 | pfleura2 | ELSE |
196 | 1 | pfleura2 | * |
197 | 1 | pfleura2 | * general case |
198 | 1 | pfleura2 | * |
199 | 1 | pfleura2 | IF( I.LT.K ) THEN |
200 | 1 | pfleura2 | IF( LSAME( STOREV, 'C' ) ) THEN |
201 | 1 | pfleura2 | VII = V( N-K+I, I ) |
202 | 1 | pfleura2 | V( N-K+I, I ) = ONE |
203 | 1 | pfleura2 | ! Skip any leading zeros. |
204 | 1 | pfleura2 | DO LASTV = 1, I-1 |
205 | 1 | pfleura2 | IF( V( LASTV, I ).NE.ZERO ) EXIT |
206 | 1 | pfleura2 | END DO |
207 | 1 | pfleura2 | J = MAX( LASTV, PREVLASTV ) |
208 | 1 | pfleura2 | * |
209 | 1 | pfleura2 | * T(i+1:k,i) := |
210 | 1 | pfleura2 | * - tau(i) * V(j:n-k+i,i+1:k)' * V(j:n-k+i,i) |
211 | 1 | pfleura2 | * |
212 | 1 | pfleura2 | CALL DGEMV( 'Transpose', N-K+I-J+1, K-I, -TAU( I ), |
213 | 1 | pfleura2 | $ V( J, I+1 ), LDV, V( J, I ), 1, ZERO, |
214 | 1 | pfleura2 | $ T( I+1, I ), 1 ) |
215 | 1 | pfleura2 | V( N-K+I, I ) = VII |
216 | 1 | pfleura2 | ELSE |
217 | 1 | pfleura2 | VII = V( I, N-K+I ) |
218 | 1 | pfleura2 | V( I, N-K+I ) = ONE |
219 | 1 | pfleura2 | ! Skip any leading zeros. |
220 | 1 | pfleura2 | DO LASTV = 1, I-1 |
221 | 1 | pfleura2 | IF( V( I, LASTV ).NE.ZERO ) EXIT |
222 | 1 | pfleura2 | END DO |
223 | 1 | pfleura2 | J = MAX( LASTV, PREVLASTV ) |
224 | 1 | pfleura2 | * |
225 | 1 | pfleura2 | * T(i+1:k,i) := |
226 | 1 | pfleura2 | * - tau(i) * V(i+1:k,j:n-k+i) * V(i,j:n-k+i)' |
227 | 1 | pfleura2 | * |
228 | 1 | pfleura2 | CALL DGEMV( 'No transpose', K-I, N-K+I-J+1, |
229 | 1 | pfleura2 | $ -TAU( I ), V( I+1, J ), LDV, V( I, J ), LDV, |
230 | 1 | pfleura2 | $ ZERO, T( I+1, I ), 1 ) |
231 | 1 | pfleura2 | V( I, N-K+I ) = VII |
232 | 1 | pfleura2 | END IF |
233 | 1 | pfleura2 | * |
234 | 1 | pfleura2 | * T(i+1:k,i) := T(i+1:k,i+1:k) * T(i+1:k,i) |
235 | 1 | pfleura2 | * |
236 | 1 | pfleura2 | CALL DTRMV( 'Lower', 'No transpose', 'Non-unit', K-I, |
237 | 1 | pfleura2 | $ T( I+1, I+1 ), LDT, T( I+1, I ), 1 ) |
238 | 1 | pfleura2 | IF( I.GT.1 ) THEN |
239 | 1 | pfleura2 | PREVLASTV = MIN( PREVLASTV, LASTV ) |
240 | 1 | pfleura2 | ELSE |
241 | 1 | pfleura2 | PREVLASTV = LASTV |
242 | 1 | pfleura2 | END IF |
243 | 1 | pfleura2 | END IF |
244 | 1 | pfleura2 | T( I, I ) = TAU( I ) |
245 | 1 | pfleura2 | END IF |
246 | 1 | pfleura2 | 40 CONTINUE |
247 | 1 | pfleura2 | END IF |
248 | 1 | pfleura2 | RETURN |
249 | 1 | pfleura2 | * |
250 | 1 | pfleura2 | * End of DLARFT |
251 | 1 | pfleura2 | * |
252 | 1 | pfleura2 | END |