root / src / lapack / double / dormqr.f @ 10
Historique | Voir | Annoter | Télécharger (7,41 ko)
1 | 1 | pfleura2 | SUBROUTINE DORMQR( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, |
---|---|---|---|
2 | 1 | pfleura2 | $ 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 |
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 | * DORMQR overwrites the general real M-by-N matrix C with |
21 | 1 | pfleura2 | * |
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 | * where Q is a real orthogonal matrix defined as the product of k |
27 | 1 | pfleura2 | * elementary reflectors |
28 | 1 | pfleura2 | * |
29 | 1 | pfleura2 | * Q = H(1) H(2) . . . H(k) |
30 | 1 | pfleura2 | * |
31 | 1 | pfleura2 | * as returned by DGEQRF. Q is of order M if SIDE = 'L' and of order N |
32 | 1 | pfleura2 | * if SIDE = 'R'. |
33 | 1 | pfleura2 | * |
34 | 1 | pfleura2 | * Arguments |
35 | 1 | pfleura2 | * ========= |
36 | 1 | pfleura2 | * |
37 | 1 | pfleura2 | * SIDE (input) CHARACTER*1 |
38 | 1 | pfleura2 | * = 'L': apply Q or Q**T from the Left; |
39 | 1 | pfleura2 | * = 'R': apply Q or Q**T from the Right. |
40 | 1 | pfleura2 | * |
41 | 1 | pfleura2 | * TRANS (input) CHARACTER*1 |
42 | 1 | pfleura2 | * = 'N': No transpose, apply Q; |
43 | 1 | pfleura2 | * = 'T': Transpose, apply Q**T. |
44 | 1 | pfleura2 | * |
45 | 1 | pfleura2 | * M (input) INTEGER |
46 | 1 | pfleura2 | * The number of rows of the matrix C. M >= 0. |
47 | 1 | pfleura2 | * |
48 | 1 | pfleura2 | * N (input) INTEGER |
49 | 1 | pfleura2 | * The number of columns of the matrix C. N >= 0. |
50 | 1 | pfleura2 | * |
51 | 1 | pfleura2 | * K (input) INTEGER |
52 | 1 | pfleura2 | * The number of elementary reflectors whose product defines |
53 | 1 | pfleura2 | * the matrix Q. |
54 | 1 | pfleura2 | * If SIDE = 'L', M >= K >= 0; |
55 | 1 | pfleura2 | * if SIDE = 'R', N >= K >= 0. |
56 | 1 | pfleura2 | * |
57 | 1 | pfleura2 | * A (input) DOUBLE PRECISION array, dimension (LDA,K) |
58 | 1 | pfleura2 | * The i-th column must contain the vector which defines the |
59 | 1 | pfleura2 | * elementary reflector H(i), for i = 1,2,...,k, as returned by |
60 | 1 | pfleura2 | * DGEQRF in the first k columns of its array argument A. |
61 | 1 | pfleura2 | * A is modified by the routine but restored on exit. |
62 | 1 | pfleura2 | * |
63 | 1 | pfleura2 | * LDA (input) INTEGER |
64 | 1 | pfleura2 | * The leading dimension of the array A. |
65 | 1 | pfleura2 | * If SIDE = 'L', LDA >= max(1,M); |
66 | 1 | pfleura2 | * if SIDE = 'R', LDA >= max(1,N). |
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), as returned by DGEQRF. |
71 | 1 | pfleura2 | * |
72 | 1 | pfleura2 | * C (input/output) DOUBLE PRECISION array, dimension (LDC,N) |
73 | 1 | pfleura2 | * On entry, the M-by-N matrix C. |
74 | 1 | pfleura2 | * On exit, C is overwritten by Q*C or Q**T*C or C*Q**T or C*Q. |
75 | 1 | pfleura2 | * |
76 | 1 | pfleura2 | * LDC (input) INTEGER |
77 | 1 | pfleura2 | * The leading dimension of the array C. LDC >= max(1,M). |
78 | 1 | pfleura2 | * |
79 | 1 | pfleura2 | * WORK (workspace/output) DOUBLE PRECISION array, dimension (MAX(1,LWORK)) |
80 | 1 | pfleura2 | * On exit, if INFO = 0, WORK(1) returns the optimal LWORK. |
81 | 1 | pfleura2 | * |
82 | 1 | pfleura2 | * LWORK (input) INTEGER |
83 | 1 | pfleura2 | * The dimension of the array WORK. |
84 | 1 | pfleura2 | * If SIDE = 'L', LWORK >= max(1,N); |
85 | 1 | pfleura2 | * if SIDE = 'R', LWORK >= max(1,M). |
86 | 1 | pfleura2 | * For optimum performance LWORK >= N*NB if SIDE = 'L', and |
87 | 1 | pfleura2 | * LWORK >= M*NB if SIDE = 'R', where NB is the optimal |
88 | 1 | pfleura2 | * blocksize. |
89 | 1 | pfleura2 | * |
90 | 1 | pfleura2 | * If LWORK = -1, then a workspace query is assumed; the routine |
91 | 1 | pfleura2 | * only calculates the optimal size of the WORK array, returns |
92 | 1 | pfleura2 | * this value as the first entry of the WORK array, and no error |
93 | 1 | pfleura2 | * message related to LWORK is issued by XERBLA. |
94 | 1 | pfleura2 | * |
95 | 1 | pfleura2 | * INFO (output) INTEGER |
96 | 1 | pfleura2 | * = 0: successful exit |
97 | 1 | pfleura2 | * < 0: if INFO = -i, the i-th argument had an illegal value |
98 | 1 | pfleura2 | * |
99 | 1 | pfleura2 | * ===================================================================== |
100 | 1 | pfleura2 | * |
101 | 1 | pfleura2 | * .. Parameters .. |
102 | 1 | pfleura2 | INTEGER NBMAX, LDT |
103 | 1 | pfleura2 | PARAMETER ( NBMAX = 64, LDT = NBMAX+1 ) |
104 | 1 | pfleura2 | * .. |
105 | 1 | pfleura2 | * .. Local Scalars .. |
106 | 1 | pfleura2 | LOGICAL LEFT, LQUERY, NOTRAN |
107 | 1 | pfleura2 | INTEGER I, I1, I2, I3, IB, IC, IINFO, IWS, JC, LDWORK, |
108 | 1 | pfleura2 | $ LWKOPT, MI, NB, NBMIN, NI, NQ, NW |
109 | 1 | pfleura2 | * .. |
110 | 1 | pfleura2 | * .. Local Arrays .. |
111 | 1 | pfleura2 | DOUBLE PRECISION T( LDT, NBMAX ) |
112 | 1 | pfleura2 | * .. |
113 | 1 | pfleura2 | * .. External Functions .. |
114 | 1 | pfleura2 | LOGICAL LSAME |
115 | 1 | pfleura2 | INTEGER ILAENV |
116 | 1 | pfleura2 | EXTERNAL LSAME, ILAENV |
117 | 1 | pfleura2 | * .. |
118 | 1 | pfleura2 | * .. External Subroutines .. |
119 | 1 | pfleura2 | EXTERNAL DLARFB, DLARFT, DORM2R, XERBLA |
120 | 1 | pfleura2 | * .. |
121 | 1 | pfleura2 | * .. Intrinsic Functions .. |
122 | 1 | pfleura2 | INTRINSIC MAX, MIN |
123 | 1 | pfleura2 | * .. |
124 | 1 | pfleura2 | * .. Executable Statements .. |
125 | 1 | pfleura2 | * |
126 | 1 | pfleura2 | * Test the input arguments |
127 | 1 | pfleura2 | * |
128 | 1 | pfleura2 | INFO = 0 |
129 | 1 | pfleura2 | LEFT = LSAME( SIDE, 'L' ) |
130 | 1 | pfleura2 | NOTRAN = LSAME( TRANS, 'N' ) |
131 | 1 | pfleura2 | LQUERY = ( LWORK.EQ.-1 ) |
132 | 1 | pfleura2 | * |
133 | 1 | pfleura2 | * NQ is the order of Q and NW is the minimum dimension of WORK |
134 | 1 | pfleura2 | * |
135 | 1 | pfleura2 | IF( LEFT ) THEN |
136 | 1 | pfleura2 | NQ = M |
137 | 1 | pfleura2 | NW = N |
138 | 1 | pfleura2 | ELSE |
139 | 1 | pfleura2 | NQ = N |
140 | 1 | pfleura2 | NW = M |
141 | 1 | pfleura2 | END IF |
142 | 1 | pfleura2 | IF( .NOT.LEFT .AND. .NOT.LSAME( SIDE, 'R' ) ) THEN |
143 | 1 | pfleura2 | INFO = -1 |
144 | 1 | pfleura2 | ELSE IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'T' ) ) THEN |
145 | 1 | pfleura2 | INFO = -2 |
146 | 1 | pfleura2 | ELSE IF( M.LT.0 ) THEN |
147 | 1 | pfleura2 | INFO = -3 |
148 | 1 | pfleura2 | ELSE IF( N.LT.0 ) THEN |
149 | 1 | pfleura2 | INFO = -4 |
150 | 1 | pfleura2 | ELSE IF( K.LT.0 .OR. K.GT.NQ ) THEN |
151 | 1 | pfleura2 | INFO = -5 |
152 | 1 | pfleura2 | ELSE IF( LDA.LT.MAX( 1, NQ ) ) THEN |
153 | 1 | pfleura2 | INFO = -7 |
154 | 1 | pfleura2 | ELSE IF( LDC.LT.MAX( 1, M ) ) THEN |
155 | 1 | pfleura2 | INFO = -10 |
156 | 1 | pfleura2 | ELSE IF( LWORK.LT.MAX( 1, NW ) .AND. .NOT.LQUERY ) THEN |
157 | 1 | pfleura2 | INFO = -12 |
158 | 1 | pfleura2 | END IF |
159 | 1 | pfleura2 | * |
160 | 1 | pfleura2 | IF( INFO.EQ.0 ) THEN |
161 | 1 | pfleura2 | * |
162 | 1 | pfleura2 | * Determine the block size. NB may be at most NBMAX, where NBMAX |
163 | 1 | pfleura2 | * is used to define the local array T. |
164 | 1 | pfleura2 | * |
165 | 1 | pfleura2 | NB = MIN( NBMAX, ILAENV( 1, 'DORMQR', SIDE // TRANS, M, N, K, |
166 | 1 | pfleura2 | $ -1 ) ) |
167 | 1 | pfleura2 | LWKOPT = MAX( 1, NW )*NB |
168 | 1 | pfleura2 | WORK( 1 ) = LWKOPT |
169 | 1 | pfleura2 | END IF |
170 | 1 | pfleura2 | * |
171 | 1 | pfleura2 | IF( INFO.NE.0 ) THEN |
172 | 1 | pfleura2 | CALL XERBLA( 'DORMQR', -INFO ) |
173 | 1 | pfleura2 | RETURN |
174 | 1 | pfleura2 | ELSE IF( LQUERY ) THEN |
175 | 1 | pfleura2 | RETURN |
176 | 1 | pfleura2 | END IF |
177 | 1 | pfleura2 | * |
178 | 1 | pfleura2 | * Quick return if possible |
179 | 1 | pfleura2 | * |
180 | 1 | pfleura2 | IF( M.EQ.0 .OR. N.EQ.0 .OR. K.EQ.0 ) THEN |
181 | 1 | pfleura2 | WORK( 1 ) = 1 |
182 | 1 | pfleura2 | RETURN |
183 | 1 | pfleura2 | END IF |
184 | 1 | pfleura2 | * |
185 | 1 | pfleura2 | NBMIN = 2 |
186 | 1 | pfleura2 | LDWORK = NW |
187 | 1 | pfleura2 | IF( NB.GT.1 .AND. NB.LT.K ) THEN |
188 | 1 | pfleura2 | IWS = NW*NB |
189 | 1 | pfleura2 | IF( LWORK.LT.IWS ) THEN |
190 | 1 | pfleura2 | NB = LWORK / LDWORK |
191 | 1 | pfleura2 | NBMIN = MAX( 2, ILAENV( 2, 'DORMQR', SIDE // TRANS, M, N, K, |
192 | 1 | pfleura2 | $ -1 ) ) |
193 | 1 | pfleura2 | END IF |
194 | 1 | pfleura2 | ELSE |
195 | 1 | pfleura2 | IWS = NW |
196 | 1 | pfleura2 | END IF |
197 | 1 | pfleura2 | * |
198 | 1 | pfleura2 | IF( NB.LT.NBMIN .OR. NB.GE.K ) THEN |
199 | 1 | pfleura2 | * |
200 | 1 | pfleura2 | * Use unblocked code |
201 | 1 | pfleura2 | * |
202 | 1 | pfleura2 | CALL DORM2R( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, |
203 | 1 | pfleura2 | $ IINFO ) |
204 | 1 | pfleura2 | ELSE |
205 | 1 | pfleura2 | * |
206 | 1 | pfleura2 | * Use blocked code |
207 | 1 | pfleura2 | * |
208 | 1 | pfleura2 | IF( ( LEFT .AND. .NOT.NOTRAN ) .OR. |
209 | 1 | pfleura2 | $ ( .NOT.LEFT .AND. NOTRAN ) ) THEN |
210 | 1 | pfleura2 | I1 = 1 |
211 | 1 | pfleura2 | I2 = K |
212 | 1 | pfleura2 | I3 = NB |
213 | 1 | pfleura2 | ELSE |
214 | 1 | pfleura2 | I1 = ( ( K-1 ) / NB )*NB + 1 |
215 | 1 | pfleura2 | I2 = 1 |
216 | 1 | pfleura2 | I3 = -NB |
217 | 1 | pfleura2 | END IF |
218 | 1 | pfleura2 | * |
219 | 1 | pfleura2 | IF( LEFT ) THEN |
220 | 1 | pfleura2 | NI = N |
221 | 1 | pfleura2 | JC = 1 |
222 | 1 | pfleura2 | ELSE |
223 | 1 | pfleura2 | MI = M |
224 | 1 | pfleura2 | IC = 1 |
225 | 1 | pfleura2 | END IF |
226 | 1 | pfleura2 | * |
227 | 1 | pfleura2 | DO 10 I = I1, I2, I3 |
228 | 1 | pfleura2 | IB = MIN( NB, K-I+1 ) |
229 | 1 | pfleura2 | * |
230 | 1 | pfleura2 | * Form the triangular factor of the block reflector |
231 | 1 | pfleura2 | * H = H(i) H(i+1) . . . H(i+ib-1) |
232 | 1 | pfleura2 | * |
233 | 1 | pfleura2 | CALL DLARFT( 'Forward', 'Columnwise', NQ-I+1, IB, A( I, I ), |
234 | 1 | pfleura2 | $ LDA, TAU( I ), T, LDT ) |
235 | 1 | pfleura2 | IF( LEFT ) THEN |
236 | 1 | pfleura2 | * |
237 | 1 | pfleura2 | * H or H' is applied to C(i:m,1:n) |
238 | 1 | pfleura2 | * |
239 | 1 | pfleura2 | MI = M - I + 1 |
240 | 1 | pfleura2 | IC = I |
241 | 1 | pfleura2 | ELSE |
242 | 1 | pfleura2 | * |
243 | 1 | pfleura2 | * H or H' is applied to C(1:m,i:n) |
244 | 1 | pfleura2 | * |
245 | 1 | pfleura2 | NI = N - I + 1 |
246 | 1 | pfleura2 | JC = I |
247 | 1 | pfleura2 | END IF |
248 | 1 | pfleura2 | * |
249 | 1 | pfleura2 | * Apply H or H' |
250 | 1 | pfleura2 | * |
251 | 1 | pfleura2 | CALL DLARFB( SIDE, TRANS, 'Forward', 'Columnwise', MI, NI, |
252 | 1 | pfleura2 | $ IB, A( I, I ), LDA, T, LDT, C( IC, JC ), LDC, |
253 | 1 | pfleura2 | $ WORK, LDWORK ) |
254 | 1 | pfleura2 | 10 CONTINUE |
255 | 1 | pfleura2 | END IF |
256 | 1 | pfleura2 | WORK( 1 ) = LWKOPT |
257 | 1 | pfleura2 | RETURN |
258 | 1 | pfleura2 | * |
259 | 1 | pfleura2 | * End of DORMQR |
260 | 1 | pfleura2 | * |
261 | 1 | pfleura2 | END |