2329
|
1 SUBROUTINE DGEBD2( M, N, A, LDA, D, E, TAUQ, TAUP, WORK, INFO ) |
|
2 * |
3333
|
3 * -- LAPACK routine (version 3.0) -- |
2329
|
4 * Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd., |
|
5 * Courant Institute, Argonne National Lab, and Rice University |
|
6 * February 29, 1992 |
|
7 * |
|
8 * .. Scalar Arguments .. |
|
9 INTEGER INFO, LDA, M, N |
|
10 * .. |
|
11 * .. Array Arguments .. |
|
12 DOUBLE PRECISION A( LDA, * ), D( * ), E( * ), TAUP( * ), |
|
13 $ TAUQ( * ), WORK( * ) |
|
14 * .. |
|
15 * |
|
16 * Purpose |
|
17 * ======= |
|
18 * |
|
19 * DGEBD2 reduces a real general m by n matrix A to upper or lower |
|
20 * bidiagonal form B by an orthogonal transformation: Q' * A * P = B. |
|
21 * |
|
22 * If m >= n, B is upper bidiagonal; if m < n, B is lower bidiagonal. |
|
23 * |
|
24 * Arguments |
|
25 * ========= |
|
26 * |
|
27 * M (input) INTEGER |
|
28 * The number of rows in the matrix A. M >= 0. |
|
29 * |
|
30 * N (input) INTEGER |
|
31 * The number of columns in the matrix A. N >= 0. |
|
32 * |
|
33 * A (input/output) DOUBLE PRECISION array, dimension (LDA,N) |
|
34 * On entry, the m by n general matrix to be reduced. |
|
35 * On exit, |
|
36 * if m >= n, the diagonal and the first superdiagonal are |
|
37 * overwritten with the upper bidiagonal matrix B; the |
|
38 * elements below the diagonal, with the array TAUQ, represent |
|
39 * the orthogonal matrix Q as a product of elementary |
|
40 * reflectors, and the elements above the first superdiagonal, |
|
41 * with the array TAUP, represent the orthogonal matrix P as |
|
42 * a product of elementary reflectors; |
|
43 * if m < n, the diagonal and the first subdiagonal are |
|
44 * overwritten with the lower bidiagonal matrix B; the |
|
45 * elements below the first subdiagonal, with the array TAUQ, |
|
46 * represent the orthogonal matrix Q as a product of |
|
47 * elementary reflectors, and the elements above the diagonal, |
|
48 * with the array TAUP, represent the orthogonal matrix P as |
|
49 * a product of elementary reflectors. |
|
50 * See Further Details. |
|
51 * |
|
52 * LDA (input) INTEGER |
|
53 * The leading dimension of the array A. LDA >= max(1,M). |
|
54 * |
|
55 * D (output) DOUBLE PRECISION array, dimension (min(M,N)) |
|
56 * The diagonal elements of the bidiagonal matrix B: |
|
57 * D(i) = A(i,i). |
|
58 * |
|
59 * E (output) DOUBLE PRECISION array, dimension (min(M,N)-1) |
|
60 * The off-diagonal elements of the bidiagonal matrix B: |
|
61 * if m >= n, E(i) = A(i,i+1) for i = 1,2,...,n-1; |
|
62 * if m < n, E(i) = A(i+1,i) for i = 1,2,...,m-1. |
|
63 * |
|
64 * TAUQ (output) DOUBLE PRECISION array dimension (min(M,N)) |
|
65 * The scalar factors of the elementary reflectors which |
|
66 * represent the orthogonal matrix Q. See Further Details. |
|
67 * |
|
68 * TAUP (output) DOUBLE PRECISION array, dimension (min(M,N)) |
|
69 * The scalar factors of the elementary reflectors which |
|
70 * represent the orthogonal matrix P. See Further Details. |
|
71 * |
|
72 * WORK (workspace) DOUBLE PRECISION array, dimension (max(M,N)) |
|
73 * |
|
74 * INFO (output) INTEGER |
|
75 * = 0: successful exit. |
|
76 * < 0: if INFO = -i, the i-th argument had an illegal value. |
|
77 * |
|
78 * Further Details |
|
79 * =============== |
|
80 * |
|
81 * The matrices Q and P are represented as products of elementary |
|
82 * reflectors: |
|
83 * |
|
84 * If m >= n, |
|
85 * |
|
86 * Q = H(1) H(2) . . . H(n) and P = G(1) G(2) . . . G(n-1) |
|
87 * |
|
88 * Each H(i) and G(i) has the form: |
|
89 * |
|
90 * H(i) = I - tauq * v * v' and G(i) = I - taup * u * u' |
|
91 * |
|
92 * where tauq and taup are real scalars, and v and u are real vectors; |
|
93 * v(1:i-1) = 0, v(i) = 1, and v(i+1:m) is stored on exit in A(i+1:m,i); |
|
94 * u(1:i) = 0, u(i+1) = 1, and u(i+2:n) is stored on exit in A(i,i+2:n); |
|
95 * tauq is stored in TAUQ(i) and taup in TAUP(i). |
|
96 * |
|
97 * If m < n, |
|
98 * |
|
99 * Q = H(1) H(2) . . . H(m-1) and P = G(1) G(2) . . . G(m) |
|
100 * |
|
101 * Each H(i) and G(i) has the form: |
|
102 * |
|
103 * H(i) = I - tauq * v * v' and G(i) = I - taup * u * u' |
|
104 * |
|
105 * where tauq and taup are real scalars, and v and u are real vectors; |
|
106 * v(1:i) = 0, v(i+1) = 1, and v(i+2:m) is stored on exit in A(i+2:m,i); |
|
107 * u(1:i-1) = 0, u(i) = 1, and u(i+1:n) is stored on exit in A(i,i+1:n); |
|
108 * tauq is stored in TAUQ(i) and taup in TAUP(i). |
|
109 * |
|
110 * The contents of A on exit are illustrated by the following examples: |
|
111 * |
|
112 * m = 6 and n = 5 (m > n): m = 5 and n = 6 (m < n): |
|
113 * |
|
114 * ( d e u1 u1 u1 ) ( d u1 u1 u1 u1 u1 ) |
|
115 * ( v1 d e u2 u2 ) ( e d u2 u2 u2 u2 ) |
|
116 * ( v1 v2 d e u3 ) ( v1 e d u3 u3 u3 ) |
|
117 * ( v1 v2 v3 d e ) ( v1 v2 e d u4 u4 ) |
|
118 * ( v1 v2 v3 v4 d ) ( v1 v2 v3 e d u5 ) |
|
119 * ( v1 v2 v3 v4 v5 ) |
|
120 * |
|
121 * where d and e denote diagonal and off-diagonal elements of B, vi |
|
122 * denotes an element of the vector defining H(i), and ui an element of |
|
123 * the vector defining G(i). |
|
124 * |
|
125 * ===================================================================== |
|
126 * |
|
127 * .. Parameters .. |
|
128 DOUBLE PRECISION ZERO, ONE |
|
129 PARAMETER ( ZERO = 0.0D+0, ONE = 1.0D+0 ) |
|
130 * .. |
|
131 * .. Local Scalars .. |
|
132 INTEGER I |
|
133 * .. |
|
134 * .. External Subroutines .. |
|
135 EXTERNAL DLARF, DLARFG, XERBLA |
|
136 * .. |
|
137 * .. Intrinsic Functions .. |
|
138 INTRINSIC MAX, MIN |
|
139 * .. |
|
140 * .. Executable Statements .. |
|
141 * |
|
142 * Test the input parameters |
|
143 * |
|
144 INFO = 0 |
|
145 IF( M.LT.0 ) THEN |
|
146 INFO = -1 |
|
147 ELSE IF( N.LT.0 ) THEN |
|
148 INFO = -2 |
|
149 ELSE IF( LDA.LT.MAX( 1, M ) ) THEN |
|
150 INFO = -4 |
|
151 END IF |
|
152 IF( INFO.LT.0 ) THEN |
|
153 CALL XERBLA( 'DGEBD2', -INFO ) |
|
154 RETURN |
|
155 END IF |
|
156 * |
|
157 IF( M.GE.N ) THEN |
|
158 * |
|
159 * Reduce to upper bidiagonal form |
|
160 * |
|
161 DO 10 I = 1, N |
|
162 * |
|
163 * Generate elementary reflector H(i) to annihilate A(i+1:m,i) |
|
164 * |
|
165 CALL DLARFG( M-I+1, A( I, I ), A( MIN( I+1, M ), I ), 1, |
|
166 $ TAUQ( I ) ) |
|
167 D( I ) = A( I, I ) |
|
168 A( I, I ) = ONE |
|
169 * |
|
170 * Apply H(i) to A(i:m,i+1:n) from the left |
|
171 * |
|
172 CALL DLARF( 'Left', M-I+1, N-I, A( I, I ), 1, TAUQ( I ), |
|
173 $ A( I, I+1 ), LDA, WORK ) |
|
174 A( I, I ) = D( I ) |
|
175 * |
|
176 IF( I.LT.N ) THEN |
|
177 * |
|
178 * Generate elementary reflector G(i) to annihilate |
|
179 * A(i,i+2:n) |
|
180 * |
|
181 CALL DLARFG( N-I, A( I, I+1 ), A( I, MIN( I+2, N ) ), |
|
182 $ LDA, TAUP( I ) ) |
|
183 E( I ) = A( I, I+1 ) |
|
184 A( I, I+1 ) = ONE |
|
185 * |
|
186 * Apply G(i) to A(i+1:m,i+1:n) from the right |
|
187 * |
|
188 CALL DLARF( 'Right', M-I, N-I, A( I, I+1 ), LDA, |
|
189 $ TAUP( I ), A( I+1, I+1 ), LDA, WORK ) |
|
190 A( I, I+1 ) = E( I ) |
|
191 ELSE |
|
192 TAUP( I ) = ZERO |
|
193 END IF |
|
194 10 CONTINUE |
|
195 ELSE |
|
196 * |
|
197 * Reduce to lower bidiagonal form |
|
198 * |
|
199 DO 20 I = 1, M |
|
200 * |
|
201 * Generate elementary reflector G(i) to annihilate A(i,i+1:n) |
|
202 * |
|
203 CALL DLARFG( N-I+1, A( I, I ), A( I, MIN( I+1, N ) ), LDA, |
|
204 $ TAUP( I ) ) |
|
205 D( I ) = A( I, I ) |
|
206 A( I, I ) = ONE |
|
207 * |
|
208 * Apply G(i) to A(i+1:m,i:n) from the right |
|
209 * |
|
210 CALL DLARF( 'Right', M-I, N-I+1, A( I, I ), LDA, TAUP( I ), |
|
211 $ A( MIN( I+1, M ), I ), LDA, WORK ) |
|
212 A( I, I ) = D( I ) |
|
213 * |
|
214 IF( I.LT.M ) THEN |
|
215 * |
|
216 * Generate elementary reflector H(i) to annihilate |
|
217 * A(i+2:m,i) |
|
218 * |
|
219 CALL DLARFG( M-I, A( I+1, I ), A( MIN( I+2, M ), I ), 1, |
|
220 $ TAUQ( I ) ) |
|
221 E( I ) = A( I+1, I ) |
|
222 A( I+1, I ) = ONE |
|
223 * |
|
224 * Apply H(i) to A(i+1:m,i+1:n) from the left |
|
225 * |
|
226 CALL DLARF( 'Left', M-I, N-I, A( I+1, I ), 1, TAUQ( I ), |
|
227 $ A( I+1, I+1 ), LDA, WORK ) |
|
228 A( I+1, I ) = E( I ) |
|
229 ELSE |
|
230 TAUQ( I ) = ZERO |
|
231 END IF |
|
232 20 CONTINUE |
|
233 END IF |
|
234 RETURN |
|
235 * |
|
236 * End of DGEBD2 |
|
237 * |
|
238 END |