root / src / lapack / double / dgeqrf.f @ 10
Historique | Voir | Annoter | Télécharger (5,74 ko)
1 | 1 | pfleura2 | SUBROUTINE DGEQRF( M, N, A, LDA, TAU, WORK, LWORK, INFO ) |
---|---|---|---|
2 | 1 | pfleura2 | * |
3 | 1 | pfleura2 | * -- LAPACK routine (version 3.2) -- |
4 | 1 | pfleura2 | * -- LAPACK is a software package provided by Univ. of Tennessee, -- |
5 | 1 | pfleura2 | * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..-- |
6 | 1 | pfleura2 | * November 2006 |
7 | 1 | pfleura2 | * |
8 | 1 | pfleura2 | * .. Scalar Arguments .. |
9 | 1 | pfleura2 | INTEGER INFO, LDA, LWORK, M, N |
10 | 1 | pfleura2 | * .. |
11 | 1 | pfleura2 | * .. Array Arguments .. |
12 | 1 | pfleura2 | DOUBLE PRECISION A( LDA, * ), TAU( * ), WORK( * ) |
13 | 1 | pfleura2 | * .. |
14 | 1 | pfleura2 | * |
15 | 1 | pfleura2 | * Purpose |
16 | 1 | pfleura2 | * ======= |
17 | 1 | pfleura2 | * |
18 | 1 | pfleura2 | * DGEQRF computes a QR factorization of a real M-by-N matrix A: |
19 | 1 | pfleura2 | * A = Q * R. |
20 | 1 | pfleura2 | * |
21 | 1 | pfleura2 | * Arguments |
22 | 1 | pfleura2 | * ========= |
23 | 1 | pfleura2 | * |
24 | 1 | pfleura2 | * M (input) INTEGER |
25 | 1 | pfleura2 | * The number of rows of the matrix A. M >= 0. |
26 | 1 | pfleura2 | * |
27 | 1 | pfleura2 | * N (input) INTEGER |
28 | 1 | pfleura2 | * The number of columns of the matrix A. N >= 0. |
29 | 1 | pfleura2 | * |
30 | 1 | pfleura2 | * A (input/output) DOUBLE PRECISION array, dimension (LDA,N) |
31 | 1 | pfleura2 | * On entry, the M-by-N matrix A. |
32 | 1 | pfleura2 | * On exit, the elements on and above the diagonal of the array |
33 | 1 | pfleura2 | * contain the min(M,N)-by-N upper trapezoidal matrix R (R is |
34 | 1 | pfleura2 | * upper triangular if m >= n); the elements below the diagonal, |
35 | 1 | pfleura2 | * with the array TAU, represent the orthogonal matrix Q as a |
36 | 1 | pfleura2 | * product of min(m,n) elementary reflectors (see Further |
37 | 1 | pfleura2 | * Details). |
38 | 1 | pfleura2 | * |
39 | 1 | pfleura2 | * LDA (input) INTEGER |
40 | 1 | pfleura2 | * The leading dimension of the array A. LDA >= max(1,M). |
41 | 1 | pfleura2 | * |
42 | 1 | pfleura2 | * TAU (output) DOUBLE PRECISION array, dimension (min(M,N)) |
43 | 1 | pfleura2 | * The scalar factors of the elementary reflectors (see Further |
44 | 1 | pfleura2 | * Details). |
45 | 1 | pfleura2 | * |
46 | 1 | pfleura2 | * WORK (workspace/output) DOUBLE PRECISION array, dimension (MAX(1,LWORK)) |
47 | 1 | pfleura2 | * On exit, if INFO = 0, WORK(1) returns the optimal LWORK. |
48 | 1 | pfleura2 | * |
49 | 1 | pfleura2 | * LWORK (input) INTEGER |
50 | 1 | pfleura2 | * The dimension of the array WORK. LWORK >= max(1,N). |
51 | 1 | pfleura2 | * For optimum performance LWORK >= N*NB, where NB is |
52 | 1 | pfleura2 | * the optimal blocksize. |
53 | 1 | pfleura2 | * |
54 | 1 | pfleura2 | * If LWORK = -1, then a workspace query is assumed; the routine |
55 | 1 | pfleura2 | * only calculates the optimal size of the WORK array, returns |
56 | 1 | pfleura2 | * this value as the first entry of the WORK array, and no error |
57 | 1 | pfleura2 | * message related to LWORK is issued by XERBLA. |
58 | 1 | pfleura2 | * |
59 | 1 | pfleura2 | * INFO (output) INTEGER |
60 | 1 | pfleura2 | * = 0: successful exit |
61 | 1 | pfleura2 | * < 0: if INFO = -i, the i-th argument had an illegal value |
62 | 1 | pfleura2 | * |
63 | 1 | pfleura2 | * Further Details |
64 | 1 | pfleura2 | * =============== |
65 | 1 | pfleura2 | * |
66 | 1 | pfleura2 | * The matrix Q is represented as a product of elementary reflectors |
67 | 1 | pfleura2 | * |
68 | 1 | pfleura2 | * Q = H(1) H(2) . . . H(k), where k = min(m,n). |
69 | 1 | pfleura2 | * |
70 | 1 | pfleura2 | * Each H(i) has the form |
71 | 1 | pfleura2 | * |
72 | 1 | pfleura2 | * H(i) = I - tau * v * v' |
73 | 1 | pfleura2 | * |
74 | 1 | pfleura2 | * where tau is a real scalar, and v is a real vector with |
75 | 1 | pfleura2 | * v(1:i-1) = 0 and v(i) = 1; v(i+1:m) is stored on exit in A(i+1:m,i), |
76 | 1 | pfleura2 | * and tau in TAU(i). |
77 | 1 | pfleura2 | * |
78 | 1 | pfleura2 | * ===================================================================== |
79 | 1 | pfleura2 | * |
80 | 1 | pfleura2 | * .. Local Scalars .. |
81 | 1 | pfleura2 | LOGICAL LQUERY |
82 | 1 | pfleura2 | INTEGER I, IB, IINFO, IWS, K, LDWORK, LWKOPT, NB, |
83 | 1 | pfleura2 | $ NBMIN, NX |
84 | 1 | pfleura2 | * .. |
85 | 1 | pfleura2 | * .. External Subroutines .. |
86 | 1 | pfleura2 | EXTERNAL DGEQR2, DLARFB, DLARFT, XERBLA |
87 | 1 | pfleura2 | * .. |
88 | 1 | pfleura2 | * .. Intrinsic Functions .. |
89 | 1 | pfleura2 | INTRINSIC MAX, MIN |
90 | 1 | pfleura2 | * .. |
91 | 1 | pfleura2 | * .. External Functions .. |
92 | 1 | pfleura2 | INTEGER ILAENV |
93 | 1 | pfleura2 | EXTERNAL ILAENV |
94 | 1 | pfleura2 | * .. |
95 | 1 | pfleura2 | * .. Executable Statements .. |
96 | 1 | pfleura2 | * |
97 | 1 | pfleura2 | * Test the input arguments |
98 | 1 | pfleura2 | * |
99 | 1 | pfleura2 | INFO = 0 |
100 | 1 | pfleura2 | NB = ILAENV( 1, 'DGEQRF', ' ', M, N, -1, -1 ) |
101 | 1 | pfleura2 | LWKOPT = N*NB |
102 | 1 | pfleura2 | WORK( 1 ) = LWKOPT |
103 | 1 | pfleura2 | LQUERY = ( LWORK.EQ.-1 ) |
104 | 1 | pfleura2 | IF( M.LT.0 ) THEN |
105 | 1 | pfleura2 | INFO = -1 |
106 | 1 | pfleura2 | ELSE IF( N.LT.0 ) THEN |
107 | 1 | pfleura2 | INFO = -2 |
108 | 1 | pfleura2 | ELSE IF( LDA.LT.MAX( 1, M ) ) THEN |
109 | 1 | pfleura2 | INFO = -4 |
110 | 1 | pfleura2 | ELSE IF( LWORK.LT.MAX( 1, N ) .AND. .NOT.LQUERY ) THEN |
111 | 1 | pfleura2 | INFO = -7 |
112 | 1 | pfleura2 | END IF |
113 | 1 | pfleura2 | IF( INFO.NE.0 ) THEN |
114 | 1 | pfleura2 | CALL XERBLA( 'DGEQRF', -INFO ) |
115 | 1 | pfleura2 | RETURN |
116 | 1 | pfleura2 | ELSE IF( LQUERY ) THEN |
117 | 1 | pfleura2 | RETURN |
118 | 1 | pfleura2 | END IF |
119 | 1 | pfleura2 | * |
120 | 1 | pfleura2 | * Quick return if possible |
121 | 1 | pfleura2 | * |
122 | 1 | pfleura2 | K = MIN( M, N ) |
123 | 1 | pfleura2 | IF( K.EQ.0 ) THEN |
124 | 1 | pfleura2 | WORK( 1 ) = 1 |
125 | 1 | pfleura2 | RETURN |
126 | 1 | pfleura2 | END IF |
127 | 1 | pfleura2 | * |
128 | 1 | pfleura2 | NBMIN = 2 |
129 | 1 | pfleura2 | NX = 0 |
130 | 1 | pfleura2 | IWS = N |
131 | 1 | pfleura2 | IF( NB.GT.1 .AND. NB.LT.K ) THEN |
132 | 1 | pfleura2 | * |
133 | 1 | pfleura2 | * Determine when to cross over from blocked to unblocked code. |
134 | 1 | pfleura2 | * |
135 | 1 | pfleura2 | NX = MAX( 0, ILAENV( 3, 'DGEQRF', ' ', M, N, -1, -1 ) ) |
136 | 1 | pfleura2 | IF( NX.LT.K ) THEN |
137 | 1 | pfleura2 | * |
138 | 1 | pfleura2 | * Determine if workspace is large enough for blocked code. |
139 | 1 | pfleura2 | * |
140 | 1 | pfleura2 | LDWORK = N |
141 | 1 | pfleura2 | IWS = LDWORK*NB |
142 | 1 | pfleura2 | IF( LWORK.LT.IWS ) THEN |
143 | 1 | pfleura2 | * |
144 | 1 | pfleura2 | * Not enough workspace to use optimal NB: reduce NB and |
145 | 1 | pfleura2 | * determine the minimum value of NB. |
146 | 1 | pfleura2 | * |
147 | 1 | pfleura2 | NB = LWORK / LDWORK |
148 | 1 | pfleura2 | NBMIN = MAX( 2, ILAENV( 2, 'DGEQRF', ' ', M, N, -1, |
149 | 1 | pfleura2 | $ -1 ) ) |
150 | 1 | pfleura2 | END IF |
151 | 1 | pfleura2 | END IF |
152 | 1 | pfleura2 | END IF |
153 | 1 | pfleura2 | * |
154 | 1 | pfleura2 | IF( NB.GE.NBMIN .AND. NB.LT.K .AND. NX.LT.K ) THEN |
155 | 1 | pfleura2 | * |
156 | 1 | pfleura2 | * Use blocked code initially |
157 | 1 | pfleura2 | * |
158 | 1 | pfleura2 | DO 10 I = 1, K - NX, NB |
159 | 1 | pfleura2 | IB = MIN( K-I+1, NB ) |
160 | 1 | pfleura2 | * |
161 | 1 | pfleura2 | * Compute the QR factorization of the current block |
162 | 1 | pfleura2 | * A(i:m,i:i+ib-1) |
163 | 1 | pfleura2 | * |
164 | 1 | pfleura2 | CALL DGEQR2( M-I+1, IB, A( I, I ), LDA, TAU( I ), WORK, |
165 | 1 | pfleura2 | $ IINFO ) |
166 | 1 | pfleura2 | IF( I+IB.LE.N ) THEN |
167 | 1 | pfleura2 | * |
168 | 1 | pfleura2 | * Form the triangular factor of the block reflector |
169 | 1 | pfleura2 | * H = H(i) H(i+1) . . . H(i+ib-1) |
170 | 1 | pfleura2 | * |
171 | 1 | pfleura2 | CALL DLARFT( 'Forward', 'Columnwise', M-I+1, IB, |
172 | 1 | pfleura2 | $ A( I, I ), LDA, TAU( I ), WORK, LDWORK ) |
173 | 1 | pfleura2 | * |
174 | 1 | pfleura2 | * Apply H' to A(i:m,i+ib:n) from the left |
175 | 1 | pfleura2 | * |
176 | 1 | pfleura2 | CALL DLARFB( 'Left', 'Transpose', 'Forward', |
177 | 1 | pfleura2 | $ 'Columnwise', M-I+1, N-I-IB+1, IB, |
178 | 1 | pfleura2 | $ A( I, I ), LDA, WORK, LDWORK, A( I, I+IB ), |
179 | 1 | pfleura2 | $ LDA, WORK( IB+1 ), LDWORK ) |
180 | 1 | pfleura2 | END IF |
181 | 1 | pfleura2 | 10 CONTINUE |
182 | 1 | pfleura2 | ELSE |
183 | 1 | pfleura2 | I = 1 |
184 | 1 | pfleura2 | END IF |
185 | 1 | pfleura2 | * |
186 | 1 | pfleura2 | * Use unblocked code to factor the last or only block. |
187 | 1 | pfleura2 | * |
188 | 1 | pfleura2 | IF( I.LE.K ) |
189 | 1 | pfleura2 | $ CALL DGEQR2( M-I+1, N-I+1, A( I, I ), LDA, TAU( I ), WORK, |
190 | 1 | pfleura2 | $ IINFO ) |
191 | 1 | pfleura2 | * |
192 | 1 | pfleura2 | WORK( 1 ) = IWS |
193 | 1 | pfleura2 | RETURN |
194 | 1 | pfleura2 | * |
195 | 1 | pfleura2 | * End of DGEQRF |
196 | 1 | pfleura2 | * |
197 | 1 | pfleura2 | END |