root / src / lapack / double / dormbr.f @ 10
Historique | Voir | Annoter | Télécharger (8,57 ko)
1 | 1 | pfleura2 | SUBROUTINE DORMBR( VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C, |
---|---|---|---|
2 | 1 | pfleura2 | $ LDC, WORK, LWORK, INFO ) |
3 | 1 | pfleura2 | * |
4 | 1 | pfleura2 | * -- LAPACK 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 SIDE, TRANS, VECT |
11 | 1 | pfleura2 | INTEGER INFO, K, LDA, LDC, LWORK, M, N |
12 | 1 | pfleura2 | * .. |
13 | 1 | pfleura2 | * .. Array Arguments .. |
14 | 1 | pfleura2 | DOUBLE PRECISION A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * ) |
15 | 1 | pfleura2 | * .. |
16 | 1 | pfleura2 | * |
17 | 1 | pfleura2 | * Purpose |
18 | 1 | pfleura2 | * ======= |
19 | 1 | pfleura2 | * |
20 | 1 | pfleura2 | * If VECT = 'Q', DORMBR overwrites the general real M-by-N matrix C |
21 | 1 | pfleura2 | * with |
22 | 1 | pfleura2 | * SIDE = 'L' SIDE = 'R' |
23 | 1 | pfleura2 | * TRANS = 'N': Q * C C * Q |
24 | 1 | pfleura2 | * TRANS = 'T': Q**T * C C * Q**T |
25 | 1 | pfleura2 | * |
26 | 1 | pfleura2 | * If VECT = 'P', DORMBR overwrites the general real M-by-N matrix C |
27 | 1 | pfleura2 | * with |
28 | 1 | pfleura2 | * SIDE = 'L' SIDE = 'R' |
29 | 1 | pfleura2 | * TRANS = 'N': P * C C * P |
30 | 1 | pfleura2 | * TRANS = 'T': P**T * C C * P**T |
31 | 1 | pfleura2 | * |
32 | 1 | pfleura2 | * Here Q and P**T are the orthogonal matrices determined by DGEBRD when |
33 | 1 | pfleura2 | * reducing a real matrix A to bidiagonal form: A = Q * B * P**T. Q and |
34 | 1 | pfleura2 | * P**T are defined as products of elementary reflectors H(i) and G(i) |
35 | 1 | pfleura2 | * respectively. |
36 | 1 | pfleura2 | * |
37 | 1 | pfleura2 | * Let nq = m if SIDE = 'L' and nq = n if SIDE = 'R'. Thus nq is the |
38 | 1 | pfleura2 | * order of the orthogonal matrix Q or P**T that is applied. |
39 | 1 | pfleura2 | * |
40 | 1 | pfleura2 | * If VECT = 'Q', A is assumed to have been an NQ-by-K matrix: |
41 | 1 | pfleura2 | * if nq >= k, Q = H(1) H(2) . . . H(k); |
42 | 1 | pfleura2 | * if nq < k, Q = H(1) H(2) . . . H(nq-1). |
43 | 1 | pfleura2 | * |
44 | 1 | pfleura2 | * If VECT = 'P', A is assumed to have been a K-by-NQ matrix: |
45 | 1 | pfleura2 | * if k < nq, P = G(1) G(2) . . . G(k); |
46 | 1 | pfleura2 | * if k >= nq, P = G(1) G(2) . . . G(nq-1). |
47 | 1 | pfleura2 | * |
48 | 1 | pfleura2 | * Arguments |
49 | 1 | pfleura2 | * ========= |
50 | 1 | pfleura2 | * |
51 | 1 | pfleura2 | * VECT (input) CHARACTER*1 |
52 | 1 | pfleura2 | * = 'Q': apply Q or Q**T; |
53 | 1 | pfleura2 | * = 'P': apply P or P**T. |
54 | 1 | pfleura2 | * |
55 | 1 | pfleura2 | * SIDE (input) CHARACTER*1 |
56 | 1 | pfleura2 | * = 'L': apply Q, Q**T, P or P**T from the Left; |
57 | 1 | pfleura2 | * = 'R': apply Q, Q**T, P or P**T from the Right. |
58 | 1 | pfleura2 | * |
59 | 1 | pfleura2 | * TRANS (input) CHARACTER*1 |
60 | 1 | pfleura2 | * = 'N': No transpose, apply Q or P; |
61 | 1 | pfleura2 | * = 'T': Transpose, apply Q**T or P**T. |
62 | 1 | pfleura2 | * |
63 | 1 | pfleura2 | * M (input) INTEGER |
64 | 1 | pfleura2 | * The number of rows of the matrix C. M >= 0. |
65 | 1 | pfleura2 | * |
66 | 1 | pfleura2 | * N (input) INTEGER |
67 | 1 | pfleura2 | * The number of columns of the matrix C. N >= 0. |
68 | 1 | pfleura2 | * |
69 | 1 | pfleura2 | * K (input) INTEGER |
70 | 1 | pfleura2 | * If VECT = 'Q', the number of columns in the original |
71 | 1 | pfleura2 | * matrix reduced by DGEBRD. |
72 | 1 | pfleura2 | * If VECT = 'P', the number of rows in the original |
73 | 1 | pfleura2 | * matrix reduced by DGEBRD. |
74 | 1 | pfleura2 | * K >= 0. |
75 | 1 | pfleura2 | * |
76 | 1 | pfleura2 | * A (input) DOUBLE PRECISION array, dimension |
77 | 1 | pfleura2 | * (LDA,min(nq,K)) if VECT = 'Q' |
78 | 1 | pfleura2 | * (LDA,nq) if VECT = 'P' |
79 | 1 | pfleura2 | * The vectors which define the elementary reflectors H(i) and |
80 | 1 | pfleura2 | * G(i), whose products determine the matrices Q and P, as |
81 | 1 | pfleura2 | * returned by DGEBRD. |
82 | 1 | pfleura2 | * |
83 | 1 | pfleura2 | * LDA (input) INTEGER |
84 | 1 | pfleura2 | * The leading dimension of the array A. |
85 | 1 | pfleura2 | * If VECT = 'Q', LDA >= max(1,nq); |
86 | 1 | pfleura2 | * if VECT = 'P', LDA >= max(1,min(nq,K)). |
87 | 1 | pfleura2 | * |
88 | 1 | pfleura2 | * TAU (input) DOUBLE PRECISION array, dimension (min(nq,K)) |
89 | 1 | pfleura2 | * TAU(i) must contain the scalar factor of the elementary |
90 | 1 | pfleura2 | * reflector H(i) or G(i) which determines Q or P, as returned |
91 | 1 | pfleura2 | * by DGEBRD in the array argument TAUQ or TAUP. |
92 | 1 | pfleura2 | * |
93 | 1 | pfleura2 | * C (input/output) DOUBLE PRECISION array, dimension (LDC,N) |
94 | 1 | pfleura2 | * On entry, the M-by-N matrix C. |
95 | 1 | pfleura2 | * On exit, C is overwritten by Q*C or Q**T*C or C*Q**T or C*Q |
96 | 1 | pfleura2 | * or P*C or P**T*C or C*P or C*P**T. |
97 | 1 | pfleura2 | * |
98 | 1 | pfleura2 | * LDC (input) INTEGER |
99 | 1 | pfleura2 | * The leading dimension of the array C. LDC >= max(1,M). |
100 | 1 | pfleura2 | * |
101 | 1 | pfleura2 | * WORK (workspace/output) DOUBLE PRECISION array, dimension (MAX(1,LWORK)) |
102 | 1 | pfleura2 | * On exit, if INFO = 0, WORK(1) returns the optimal LWORK. |
103 | 1 | pfleura2 | * |
104 | 1 | pfleura2 | * LWORK (input) INTEGER |
105 | 1 | pfleura2 | * The dimension of the array WORK. |
106 | 1 | pfleura2 | * If SIDE = 'L', LWORK >= max(1,N); |
107 | 1 | pfleura2 | * if SIDE = 'R', LWORK >= max(1,M). |
108 | 1 | pfleura2 | * For optimum performance LWORK >= N*NB if SIDE = 'L', and |
109 | 1 | pfleura2 | * LWORK >= M*NB if SIDE = 'R', where NB is the optimal |
110 | 1 | pfleura2 | * blocksize. |
111 | 1 | pfleura2 | * |
112 | 1 | pfleura2 | * If LWORK = -1, then a workspace query is assumed; the routine |
113 | 1 | pfleura2 | * only calculates the optimal size of the WORK array, returns |
114 | 1 | pfleura2 | * this value as the first entry of the WORK array, and no error |
115 | 1 | pfleura2 | * message related to LWORK is issued by XERBLA. |
116 | 1 | pfleura2 | * |
117 | 1 | pfleura2 | * INFO (output) INTEGER |
118 | 1 | pfleura2 | * = 0: successful exit |
119 | 1 | pfleura2 | * < 0: if INFO = -i, the i-th argument had an illegal value |
120 | 1 | pfleura2 | * |
121 | 1 | pfleura2 | * ===================================================================== |
122 | 1 | pfleura2 | * |
123 | 1 | pfleura2 | * .. Local Scalars .. |
124 | 1 | pfleura2 | LOGICAL APPLYQ, LEFT, LQUERY, NOTRAN |
125 | 1 | pfleura2 | CHARACTER TRANST |
126 | 1 | pfleura2 | INTEGER I1, I2, IINFO, LWKOPT, MI, NB, NI, NQ, NW |
127 | 1 | pfleura2 | * .. |
128 | 1 | pfleura2 | * .. External Functions .. |
129 | 1 | pfleura2 | LOGICAL LSAME |
130 | 1 | pfleura2 | INTEGER ILAENV |
131 | 1 | pfleura2 | EXTERNAL LSAME, ILAENV |
132 | 1 | pfleura2 | * .. |
133 | 1 | pfleura2 | * .. External Subroutines .. |
134 | 1 | pfleura2 | EXTERNAL DORMLQ, DORMQR, XERBLA |
135 | 1 | pfleura2 | * .. |
136 | 1 | pfleura2 | * .. Intrinsic Functions .. |
137 | 1 | pfleura2 | INTRINSIC MAX, MIN |
138 | 1 | pfleura2 | * .. |
139 | 1 | pfleura2 | * .. Executable Statements .. |
140 | 1 | pfleura2 | * |
141 | 1 | pfleura2 | * Test the input arguments |
142 | 1 | pfleura2 | * |
143 | 1 | pfleura2 | INFO = 0 |
144 | 1 | pfleura2 | APPLYQ = LSAME( VECT, 'Q' ) |
145 | 1 | pfleura2 | LEFT = LSAME( SIDE, 'L' ) |
146 | 1 | pfleura2 | NOTRAN = LSAME( TRANS, 'N' ) |
147 | 1 | pfleura2 | LQUERY = ( LWORK.EQ.-1 ) |
148 | 1 | pfleura2 | * |
149 | 1 | pfleura2 | * NQ is the order of Q or P and NW is the minimum dimension of WORK |
150 | 1 | pfleura2 | * |
151 | 1 | pfleura2 | IF( LEFT ) THEN |
152 | 1 | pfleura2 | NQ = M |
153 | 1 | pfleura2 | NW = N |
154 | 1 | pfleura2 | ELSE |
155 | 1 | pfleura2 | NQ = N |
156 | 1 | pfleura2 | NW = M |
157 | 1 | pfleura2 | END IF |
158 | 1 | pfleura2 | IF( .NOT.APPLYQ .AND. .NOT.LSAME( VECT, 'P' ) ) THEN |
159 | 1 | pfleura2 | INFO = -1 |
160 | 1 | pfleura2 | ELSE IF( .NOT.LEFT .AND. .NOT.LSAME( SIDE, 'R' ) ) THEN |
161 | 1 | pfleura2 | INFO = -2 |
162 | 1 | pfleura2 | ELSE IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'T' ) ) THEN |
163 | 1 | pfleura2 | INFO = -3 |
164 | 1 | pfleura2 | ELSE IF( M.LT.0 ) THEN |
165 | 1 | pfleura2 | INFO = -4 |
166 | 1 | pfleura2 | ELSE IF( N.LT.0 ) THEN |
167 | 1 | pfleura2 | INFO = -5 |
168 | 1 | pfleura2 | ELSE IF( K.LT.0 ) THEN |
169 | 1 | pfleura2 | INFO = -6 |
170 | 1 | pfleura2 | ELSE IF( ( APPLYQ .AND. LDA.LT.MAX( 1, NQ ) ) .OR. |
171 | 1 | pfleura2 | $ ( .NOT.APPLYQ .AND. LDA.LT.MAX( 1, MIN( NQ, K ) ) ) ) |
172 | 1 | pfleura2 | $ THEN |
173 | 1 | pfleura2 | INFO = -8 |
174 | 1 | pfleura2 | ELSE IF( LDC.LT.MAX( 1, M ) ) THEN |
175 | 1 | pfleura2 | INFO = -11 |
176 | 1 | pfleura2 | ELSE IF( LWORK.LT.MAX( 1, NW ) .AND. .NOT.LQUERY ) THEN |
177 | 1 | pfleura2 | INFO = -13 |
178 | 1 | pfleura2 | END IF |
179 | 1 | pfleura2 | * |
180 | 1 | pfleura2 | IF( INFO.EQ.0 ) THEN |
181 | 1 | pfleura2 | IF( APPLYQ ) THEN |
182 | 1 | pfleura2 | IF( LEFT ) THEN |
183 | 1 | pfleura2 | NB = ILAENV( 1, 'DORMQR', SIDE // TRANS, M-1, N, M-1, |
184 | 1 | pfleura2 | $ -1 ) |
185 | 1 | pfleura2 | ELSE |
186 | 1 | pfleura2 | NB = ILAENV( 1, 'DORMQR', SIDE // TRANS, M, N-1, N-1, |
187 | 1 | pfleura2 | $ -1 ) |
188 | 1 | pfleura2 | END IF |
189 | 1 | pfleura2 | ELSE |
190 | 1 | pfleura2 | IF( LEFT ) THEN |
191 | 1 | pfleura2 | NB = ILAENV( 1, 'DORMLQ', SIDE // TRANS, M-1, N, M-1, |
192 | 1 | pfleura2 | $ -1 ) |
193 | 1 | pfleura2 | ELSE |
194 | 1 | pfleura2 | NB = ILAENV( 1, 'DORMLQ', SIDE // TRANS, M, N-1, N-1, |
195 | 1 | pfleura2 | $ -1 ) |
196 | 1 | pfleura2 | END IF |
197 | 1 | pfleura2 | END IF |
198 | 1 | pfleura2 | LWKOPT = MAX( 1, NW )*NB |
199 | 1 | pfleura2 | WORK( 1 ) = LWKOPT |
200 | 1 | pfleura2 | END IF |
201 | 1 | pfleura2 | * |
202 | 1 | pfleura2 | IF( INFO.NE.0 ) THEN |
203 | 1 | pfleura2 | CALL XERBLA( 'DORMBR', -INFO ) |
204 | 1 | pfleura2 | RETURN |
205 | 1 | pfleura2 | ELSE IF( LQUERY ) THEN |
206 | 1 | pfleura2 | RETURN |
207 | 1 | pfleura2 | END IF |
208 | 1 | pfleura2 | * |
209 | 1 | pfleura2 | * Quick return if possible |
210 | 1 | pfleura2 | * |
211 | 1 | pfleura2 | WORK( 1 ) = 1 |
212 | 1 | pfleura2 | IF( M.EQ.0 .OR. N.EQ.0 ) |
213 | 1 | pfleura2 | $ RETURN |
214 | 1 | pfleura2 | * |
215 | 1 | pfleura2 | IF( APPLYQ ) THEN |
216 | 1 | pfleura2 | * |
217 | 1 | pfleura2 | * Apply Q |
218 | 1 | pfleura2 | * |
219 | 1 | pfleura2 | IF( NQ.GE.K ) THEN |
220 | 1 | pfleura2 | * |
221 | 1 | pfleura2 | * Q was determined by a call to DGEBRD with nq >= k |
222 | 1 | pfleura2 | * |
223 | 1 | pfleura2 | CALL DORMQR( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, |
224 | 1 | pfleura2 | $ WORK, LWORK, IINFO ) |
225 | 1 | pfleura2 | ELSE IF( NQ.GT.1 ) THEN |
226 | 1 | pfleura2 | * |
227 | 1 | pfleura2 | * Q was determined by a call to DGEBRD with nq < k |
228 | 1 | pfleura2 | * |
229 | 1 | pfleura2 | IF( LEFT ) THEN |
230 | 1 | pfleura2 | MI = M - 1 |
231 | 1 | pfleura2 | NI = N |
232 | 1 | pfleura2 | I1 = 2 |
233 | 1 | pfleura2 | I2 = 1 |
234 | 1 | pfleura2 | ELSE |
235 | 1 | pfleura2 | MI = M |
236 | 1 | pfleura2 | NI = N - 1 |
237 | 1 | pfleura2 | I1 = 1 |
238 | 1 | pfleura2 | I2 = 2 |
239 | 1 | pfleura2 | END IF |
240 | 1 | pfleura2 | CALL DORMQR( SIDE, TRANS, MI, NI, NQ-1, A( 2, 1 ), LDA, TAU, |
241 | 1 | pfleura2 | $ C( I1, I2 ), LDC, WORK, LWORK, IINFO ) |
242 | 1 | pfleura2 | END IF |
243 | 1 | pfleura2 | ELSE |
244 | 1 | pfleura2 | * |
245 | 1 | pfleura2 | * Apply P |
246 | 1 | pfleura2 | * |
247 | 1 | pfleura2 | IF( NOTRAN ) THEN |
248 | 1 | pfleura2 | TRANST = 'T' |
249 | 1 | pfleura2 | ELSE |
250 | 1 | pfleura2 | TRANST = 'N' |
251 | 1 | pfleura2 | END IF |
252 | 1 | pfleura2 | IF( NQ.GT.K ) THEN |
253 | 1 | pfleura2 | * |
254 | 1 | pfleura2 | * P was determined by a call to DGEBRD with nq > k |
255 | 1 | pfleura2 | * |
256 | 1 | pfleura2 | CALL DORMLQ( SIDE, TRANST, M, N, K, A, LDA, TAU, C, LDC, |
257 | 1 | pfleura2 | $ WORK, LWORK, IINFO ) |
258 | 1 | pfleura2 | ELSE IF( NQ.GT.1 ) THEN |
259 | 1 | pfleura2 | * |
260 | 1 | pfleura2 | * P was determined by a call to DGEBRD with nq <= k |
261 | 1 | pfleura2 | * |
262 | 1 | pfleura2 | IF( LEFT ) THEN |
263 | 1 | pfleura2 | MI = M - 1 |
264 | 1 | pfleura2 | NI = N |
265 | 1 | pfleura2 | I1 = 2 |
266 | 1 | pfleura2 | I2 = 1 |
267 | 1 | pfleura2 | ELSE |
268 | 1 | pfleura2 | MI = M |
269 | 1 | pfleura2 | NI = N - 1 |
270 | 1 | pfleura2 | I1 = 1 |
271 | 1 | pfleura2 | I2 = 2 |
272 | 1 | pfleura2 | END IF |
273 | 1 | pfleura2 | CALL DORMLQ( SIDE, TRANST, MI, NI, NQ-1, A( 1, 2 ), LDA, |
274 | 1 | pfleura2 | $ TAU, C( I1, I2 ), LDC, WORK, LWORK, IINFO ) |
275 | 1 | pfleura2 | END IF |
276 | 1 | pfleura2 | END IF |
277 | 1 | pfleura2 | WORK( 1 ) = LWKOPT |
278 | 1 | pfleura2 | RETURN |
279 | 1 | pfleura2 | * |
280 | 1 | pfleura2 | * End of DORMBR |
281 | 1 | pfleura2 | * |
282 | 1 | pfleura2 | END |