root / src / lapack / double / dlasdq.f @ 10
Historique | Voir | Annoter | Télécharger (10,39 ko)
1 | 1 | pfleura2 | SUBROUTINE DLASDQ( UPLO, SQRE, N, NCVT, NRU, NCC, D, E, VT, LDVT, |
---|---|---|---|
2 | 1 | pfleura2 | $ U, LDU, C, LDC, WORK, INFO ) |
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 UPLO |
11 | 1 | pfleura2 | INTEGER INFO, LDC, LDU, LDVT, N, NCC, NCVT, NRU, SQRE |
12 | 1 | pfleura2 | * .. |
13 | 1 | pfleura2 | * .. Array Arguments .. |
14 | 1 | pfleura2 | DOUBLE PRECISION C( LDC, * ), D( * ), E( * ), U( LDU, * ), |
15 | 1 | pfleura2 | $ VT( LDVT, * ), WORK( * ) |
16 | 1 | pfleura2 | * .. |
17 | 1 | pfleura2 | * |
18 | 1 | pfleura2 | * Purpose |
19 | 1 | pfleura2 | * ======= |
20 | 1 | pfleura2 | * |
21 | 1 | pfleura2 | * DLASDQ computes the singular value decomposition (SVD) of a real |
22 | 1 | pfleura2 | * (upper or lower) bidiagonal matrix with diagonal D and offdiagonal |
23 | 1 | pfleura2 | * E, accumulating the transformations if desired. Letting B denote |
24 | 1 | pfleura2 | * the input bidiagonal matrix, the algorithm computes orthogonal |
25 | 1 | pfleura2 | * matrices Q and P such that B = Q * S * P' (P' denotes the transpose |
26 | 1 | pfleura2 | * of P). The singular values S are overwritten on D. |
27 | 1 | pfleura2 | * |
28 | 1 | pfleura2 | * The input matrix U is changed to U * Q if desired. |
29 | 1 | pfleura2 | * The input matrix VT is changed to P' * VT if desired. |
30 | 1 | pfleura2 | * The input matrix C is changed to Q' * C if desired. |
31 | 1 | pfleura2 | * |
32 | 1 | pfleura2 | * See "Computing Small Singular Values of Bidiagonal Matrices With |
33 | 1 | pfleura2 | * Guaranteed High Relative Accuracy," by J. Demmel and W. Kahan, |
34 | 1 | pfleura2 | * LAPACK Working Note #3, for a detailed description of the algorithm. |
35 | 1 | pfleura2 | * |
36 | 1 | pfleura2 | * Arguments |
37 | 1 | pfleura2 | * ========= |
38 | 1 | pfleura2 | * |
39 | 1 | pfleura2 | * UPLO (input) CHARACTER*1 |
40 | 1 | pfleura2 | * On entry, UPLO specifies whether the input bidiagonal matrix |
41 | 1 | pfleura2 | * is upper or lower bidiagonal, and wether it is square are |
42 | 1 | pfleura2 | * not. |
43 | 1 | pfleura2 | * UPLO = 'U' or 'u' B is upper bidiagonal. |
44 | 1 | pfleura2 | * UPLO = 'L' or 'l' B is lower bidiagonal. |
45 | 1 | pfleura2 | * |
46 | 1 | pfleura2 | * SQRE (input) INTEGER |
47 | 1 | pfleura2 | * = 0: then the input matrix is N-by-N. |
48 | 1 | pfleura2 | * = 1: then the input matrix is N-by-(N+1) if UPLU = 'U' and |
49 | 1 | pfleura2 | * (N+1)-by-N if UPLU = 'L'. |
50 | 1 | pfleura2 | * |
51 | 1 | pfleura2 | * The bidiagonal matrix has |
52 | 1 | pfleura2 | * N = NL + NR + 1 rows and |
53 | 1 | pfleura2 | * M = N + SQRE >= N columns. |
54 | 1 | pfleura2 | * |
55 | 1 | pfleura2 | * N (input) INTEGER |
56 | 1 | pfleura2 | * On entry, N specifies the number of rows and columns |
57 | 1 | pfleura2 | * in the matrix. N must be at least 0. |
58 | 1 | pfleura2 | * |
59 | 1 | pfleura2 | * NCVT (input) INTEGER |
60 | 1 | pfleura2 | * On entry, NCVT specifies the number of columns of |
61 | 1 | pfleura2 | * the matrix VT. NCVT must be at least 0. |
62 | 1 | pfleura2 | * |
63 | 1 | pfleura2 | * NRU (input) INTEGER |
64 | 1 | pfleura2 | * On entry, NRU specifies the number of rows of |
65 | 1 | pfleura2 | * the matrix U. NRU must be at least 0. |
66 | 1 | pfleura2 | * |
67 | 1 | pfleura2 | * NCC (input) INTEGER |
68 | 1 | pfleura2 | * On entry, NCC specifies the number of columns of |
69 | 1 | pfleura2 | * the matrix C. NCC must be at least 0. |
70 | 1 | pfleura2 | * |
71 | 1 | pfleura2 | * D (input/output) DOUBLE PRECISION array, dimension (N) |
72 | 1 | pfleura2 | * On entry, D contains the diagonal entries of the |
73 | 1 | pfleura2 | * bidiagonal matrix whose SVD is desired. On normal exit, |
74 | 1 | pfleura2 | * D contains the singular values in ascending order. |
75 | 1 | pfleura2 | * |
76 | 1 | pfleura2 | * E (input/output) DOUBLE PRECISION array. |
77 | 1 | pfleura2 | * dimension is (N-1) if SQRE = 0 and N if SQRE = 1. |
78 | 1 | pfleura2 | * On entry, the entries of E contain the offdiagonal entries |
79 | 1 | pfleura2 | * of the bidiagonal matrix whose SVD is desired. On normal |
80 | 1 | pfleura2 | * exit, E will contain 0. If the algorithm does not converge, |
81 | 1 | pfleura2 | * D and E will contain the diagonal and superdiagonal entries |
82 | 1 | pfleura2 | * of a bidiagonal matrix orthogonally equivalent to the one |
83 | 1 | pfleura2 | * given as input. |
84 | 1 | pfleura2 | * |
85 | 1 | pfleura2 | * VT (input/output) DOUBLE PRECISION array, dimension (LDVT, NCVT) |
86 | 1 | pfleura2 | * On entry, contains a matrix which on exit has been |
87 | 1 | pfleura2 | * premultiplied by P', dimension N-by-NCVT if SQRE = 0 |
88 | 1 | pfleura2 | * and (N+1)-by-NCVT if SQRE = 1 (not referenced if NCVT=0). |
89 | 1 | pfleura2 | * |
90 | 1 | pfleura2 | * LDVT (input) INTEGER |
91 | 1 | pfleura2 | * On entry, LDVT specifies the leading dimension of VT as |
92 | 1 | pfleura2 | * declared in the calling (sub) program. LDVT must be at |
93 | 1 | pfleura2 | * least 1. If NCVT is nonzero LDVT must also be at least N. |
94 | 1 | pfleura2 | * |
95 | 1 | pfleura2 | * U (input/output) DOUBLE PRECISION array, dimension (LDU, N) |
96 | 1 | pfleura2 | * On entry, contains a matrix which on exit has been |
97 | 1 | pfleura2 | * postmultiplied by Q, dimension NRU-by-N if SQRE = 0 |
98 | 1 | pfleura2 | * and NRU-by-(N+1) if SQRE = 1 (not referenced if NRU=0). |
99 | 1 | pfleura2 | * |
100 | 1 | pfleura2 | * LDU (input) INTEGER |
101 | 1 | pfleura2 | * On entry, LDU specifies the leading dimension of U as |
102 | 1 | pfleura2 | * declared in the calling (sub) program. LDU must be at |
103 | 1 | pfleura2 | * least max( 1, NRU ) . |
104 | 1 | pfleura2 | * |
105 | 1 | pfleura2 | * C (input/output) DOUBLE PRECISION array, dimension (LDC, NCC) |
106 | 1 | pfleura2 | * On entry, contains an N-by-NCC matrix which on exit |
107 | 1 | pfleura2 | * has been premultiplied by Q' dimension N-by-NCC if SQRE = 0 |
108 | 1 | pfleura2 | * and (N+1)-by-NCC if SQRE = 1 (not referenced if NCC=0). |
109 | 1 | pfleura2 | * |
110 | 1 | pfleura2 | * LDC (input) INTEGER |
111 | 1 | pfleura2 | * On entry, LDC specifies the leading dimension of C as |
112 | 1 | pfleura2 | * declared in the calling (sub) program. LDC must be at |
113 | 1 | pfleura2 | * least 1. If NCC is nonzero, LDC must also be at least N. |
114 | 1 | pfleura2 | * |
115 | 1 | pfleura2 | * WORK (workspace) DOUBLE PRECISION array, dimension (4*N) |
116 | 1 | pfleura2 | * Workspace. Only referenced if one of NCVT, NRU, or NCC is |
117 | 1 | pfleura2 | * nonzero, and if N is at least 2. |
118 | 1 | pfleura2 | * |
119 | 1 | pfleura2 | * INFO (output) INTEGER |
120 | 1 | pfleura2 | * On exit, a value of 0 indicates a successful exit. |
121 | 1 | pfleura2 | * If INFO < 0, argument number -INFO is illegal. |
122 | 1 | pfleura2 | * If INFO > 0, the algorithm did not converge, and INFO |
123 | 1 | pfleura2 | * specifies how many superdiagonals did not converge. |
124 | 1 | pfleura2 | * |
125 | 1 | pfleura2 | * Further Details |
126 | 1 | pfleura2 | * =============== |
127 | 1 | pfleura2 | * |
128 | 1 | pfleura2 | * Based on contributions by |
129 | 1 | pfleura2 | * Ming Gu and Huan Ren, Computer Science Division, University of |
130 | 1 | pfleura2 | * California at Berkeley, USA |
131 | 1 | pfleura2 | * |
132 | 1 | pfleura2 | * ===================================================================== |
133 | 1 | pfleura2 | * |
134 | 1 | pfleura2 | * .. Parameters .. |
135 | 1 | pfleura2 | DOUBLE PRECISION ZERO |
136 | 1 | pfleura2 | PARAMETER ( ZERO = 0.0D+0 ) |
137 | 1 | pfleura2 | * .. |
138 | 1 | pfleura2 | * .. Local Scalars .. |
139 | 1 | pfleura2 | LOGICAL ROTATE |
140 | 1 | pfleura2 | INTEGER I, ISUB, IUPLO, J, NP1, SQRE1 |
141 | 1 | pfleura2 | DOUBLE PRECISION CS, R, SMIN, SN |
142 | 1 | pfleura2 | * .. |
143 | 1 | pfleura2 | * .. External Subroutines .. |
144 | 1 | pfleura2 | EXTERNAL DBDSQR, DLARTG, DLASR, DSWAP, XERBLA |
145 | 1 | pfleura2 | * .. |
146 | 1 | pfleura2 | * .. External Functions .. |
147 | 1 | pfleura2 | LOGICAL LSAME |
148 | 1 | pfleura2 | EXTERNAL LSAME |
149 | 1 | pfleura2 | * .. |
150 | 1 | pfleura2 | * .. Intrinsic Functions .. |
151 | 1 | pfleura2 | INTRINSIC MAX |
152 | 1 | pfleura2 | * .. |
153 | 1 | pfleura2 | * .. Executable Statements .. |
154 | 1 | pfleura2 | * |
155 | 1 | pfleura2 | * Test the input parameters. |
156 | 1 | pfleura2 | * |
157 | 1 | pfleura2 | INFO = 0 |
158 | 1 | pfleura2 | IUPLO = 0 |
159 | 1 | pfleura2 | IF( LSAME( UPLO, 'U' ) ) |
160 | 1 | pfleura2 | $ IUPLO = 1 |
161 | 1 | pfleura2 | IF( LSAME( UPLO, 'L' ) ) |
162 | 1 | pfleura2 | $ IUPLO = 2 |
163 | 1 | pfleura2 | IF( IUPLO.EQ.0 ) THEN |
164 | 1 | pfleura2 | INFO = -1 |
165 | 1 | pfleura2 | ELSE IF( ( SQRE.LT.0 ) .OR. ( SQRE.GT.1 ) ) THEN |
166 | 1 | pfleura2 | INFO = -2 |
167 | 1 | pfleura2 | ELSE IF( N.LT.0 ) THEN |
168 | 1 | pfleura2 | INFO = -3 |
169 | 1 | pfleura2 | ELSE IF( NCVT.LT.0 ) THEN |
170 | 1 | pfleura2 | INFO = -4 |
171 | 1 | pfleura2 | ELSE IF( NRU.LT.0 ) THEN |
172 | 1 | pfleura2 | INFO = -5 |
173 | 1 | pfleura2 | ELSE IF( NCC.LT.0 ) THEN |
174 | 1 | pfleura2 | INFO = -6 |
175 | 1 | pfleura2 | ELSE IF( ( NCVT.EQ.0 .AND. LDVT.LT.1 ) .OR. |
176 | 1 | pfleura2 | $ ( NCVT.GT.0 .AND. LDVT.LT.MAX( 1, N ) ) ) THEN |
177 | 1 | pfleura2 | INFO = -10 |
178 | 1 | pfleura2 | ELSE IF( LDU.LT.MAX( 1, NRU ) ) THEN |
179 | 1 | pfleura2 | INFO = -12 |
180 | 1 | pfleura2 | ELSE IF( ( NCC.EQ.0 .AND. LDC.LT.1 ) .OR. |
181 | 1 | pfleura2 | $ ( NCC.GT.0 .AND. LDC.LT.MAX( 1, N ) ) ) THEN |
182 | 1 | pfleura2 | INFO = -14 |
183 | 1 | pfleura2 | END IF |
184 | 1 | pfleura2 | IF( INFO.NE.0 ) THEN |
185 | 1 | pfleura2 | CALL XERBLA( 'DLASDQ', -INFO ) |
186 | 1 | pfleura2 | RETURN |
187 | 1 | pfleura2 | END IF |
188 | 1 | pfleura2 | IF( N.EQ.0 ) |
189 | 1 | pfleura2 | $ RETURN |
190 | 1 | pfleura2 | * |
191 | 1 | pfleura2 | * ROTATE is true if any singular vectors desired, false otherwise |
192 | 1 | pfleura2 | * |
193 | 1 | pfleura2 | ROTATE = ( NCVT.GT.0 ) .OR. ( NRU.GT.0 ) .OR. ( NCC.GT.0 ) |
194 | 1 | pfleura2 | NP1 = N + 1 |
195 | 1 | pfleura2 | SQRE1 = SQRE |
196 | 1 | pfleura2 | * |
197 | 1 | pfleura2 | * If matrix non-square upper bidiagonal, rotate to be lower |
198 | 1 | pfleura2 | * bidiagonal. The rotations are on the right. |
199 | 1 | pfleura2 | * |
200 | 1 | pfleura2 | IF( ( IUPLO.EQ.1 ) .AND. ( SQRE1.EQ.1 ) ) THEN |
201 | 1 | pfleura2 | DO 10 I = 1, N - 1 |
202 | 1 | pfleura2 | CALL DLARTG( D( I ), E( I ), CS, SN, R ) |
203 | 1 | pfleura2 | D( I ) = R |
204 | 1 | pfleura2 | E( I ) = SN*D( I+1 ) |
205 | 1 | pfleura2 | D( I+1 ) = CS*D( I+1 ) |
206 | 1 | pfleura2 | IF( ROTATE ) THEN |
207 | 1 | pfleura2 | WORK( I ) = CS |
208 | 1 | pfleura2 | WORK( N+I ) = SN |
209 | 1 | pfleura2 | END IF |
210 | 1 | pfleura2 | 10 CONTINUE |
211 | 1 | pfleura2 | CALL DLARTG( D( N ), E( N ), CS, SN, R ) |
212 | 1 | pfleura2 | D( N ) = R |
213 | 1 | pfleura2 | E( N ) = ZERO |
214 | 1 | pfleura2 | IF( ROTATE ) THEN |
215 | 1 | pfleura2 | WORK( N ) = CS |
216 | 1 | pfleura2 | WORK( N+N ) = SN |
217 | 1 | pfleura2 | END IF |
218 | 1 | pfleura2 | IUPLO = 2 |
219 | 1 | pfleura2 | SQRE1 = 0 |
220 | 1 | pfleura2 | * |
221 | 1 | pfleura2 | * Update singular vectors if desired. |
222 | 1 | pfleura2 | * |
223 | 1 | pfleura2 | IF( NCVT.GT.0 ) |
224 | 1 | pfleura2 | $ CALL DLASR( 'L', 'V', 'F', NP1, NCVT, WORK( 1 ), |
225 | 1 | pfleura2 | $ WORK( NP1 ), VT, LDVT ) |
226 | 1 | pfleura2 | END IF |
227 | 1 | pfleura2 | * |
228 | 1 | pfleura2 | * If matrix lower bidiagonal, rotate to be upper bidiagonal |
229 | 1 | pfleura2 | * by applying Givens rotations on the left. |
230 | 1 | pfleura2 | * |
231 | 1 | pfleura2 | IF( IUPLO.EQ.2 ) THEN |
232 | 1 | pfleura2 | DO 20 I = 1, N - 1 |
233 | 1 | pfleura2 | CALL DLARTG( D( I ), E( I ), CS, SN, R ) |
234 | 1 | pfleura2 | D( I ) = R |
235 | 1 | pfleura2 | E( I ) = SN*D( I+1 ) |
236 | 1 | pfleura2 | D( I+1 ) = CS*D( I+1 ) |
237 | 1 | pfleura2 | IF( ROTATE ) THEN |
238 | 1 | pfleura2 | WORK( I ) = CS |
239 | 1 | pfleura2 | WORK( N+I ) = SN |
240 | 1 | pfleura2 | END IF |
241 | 1 | pfleura2 | 20 CONTINUE |
242 | 1 | pfleura2 | * |
243 | 1 | pfleura2 | * If matrix (N+1)-by-N lower bidiagonal, one additional |
244 | 1 | pfleura2 | * rotation is needed. |
245 | 1 | pfleura2 | * |
246 | 1 | pfleura2 | IF( SQRE1.EQ.1 ) THEN |
247 | 1 | pfleura2 | CALL DLARTG( D( N ), E( N ), CS, SN, R ) |
248 | 1 | pfleura2 | D( N ) = R |
249 | 1 | pfleura2 | IF( ROTATE ) THEN |
250 | 1 | pfleura2 | WORK( N ) = CS |
251 | 1 | pfleura2 | WORK( N+N ) = SN |
252 | 1 | pfleura2 | END IF |
253 | 1 | pfleura2 | END IF |
254 | 1 | pfleura2 | * |
255 | 1 | pfleura2 | * Update singular vectors if desired. |
256 | 1 | pfleura2 | * |
257 | 1 | pfleura2 | IF( NRU.GT.0 ) THEN |
258 | 1 | pfleura2 | IF( SQRE1.EQ.0 ) THEN |
259 | 1 | pfleura2 | CALL DLASR( 'R', 'V', 'F', NRU, N, WORK( 1 ), |
260 | 1 | pfleura2 | $ WORK( NP1 ), U, LDU ) |
261 | 1 | pfleura2 | ELSE |
262 | 1 | pfleura2 | CALL DLASR( 'R', 'V', 'F', NRU, NP1, WORK( 1 ), |
263 | 1 | pfleura2 | $ WORK( NP1 ), U, LDU ) |
264 | 1 | pfleura2 | END IF |
265 | 1 | pfleura2 | END IF |
266 | 1 | pfleura2 | IF( NCC.GT.0 ) THEN |
267 | 1 | pfleura2 | IF( SQRE1.EQ.0 ) THEN |
268 | 1 | pfleura2 | CALL DLASR( 'L', 'V', 'F', N, NCC, WORK( 1 ), |
269 | 1 | pfleura2 | $ WORK( NP1 ), C, LDC ) |
270 | 1 | pfleura2 | ELSE |
271 | 1 | pfleura2 | CALL DLASR( 'L', 'V', 'F', NP1, NCC, WORK( 1 ), |
272 | 1 | pfleura2 | $ WORK( NP1 ), C, LDC ) |
273 | 1 | pfleura2 | END IF |
274 | 1 | pfleura2 | END IF |
275 | 1 | pfleura2 | END IF |
276 | 1 | pfleura2 | * |
277 | 1 | pfleura2 | * Call DBDSQR to compute the SVD of the reduced real |
278 | 1 | pfleura2 | * N-by-N upper bidiagonal matrix. |
279 | 1 | pfleura2 | * |
280 | 1 | pfleura2 | CALL DBDSQR( 'U', N, NCVT, NRU, NCC, D, E, VT, LDVT, U, LDU, C, |
281 | 1 | pfleura2 | $ LDC, WORK, INFO ) |
282 | 1 | pfleura2 | * |
283 | 1 | pfleura2 | * Sort the singular values into ascending order (insertion sort on |
284 | 1 | pfleura2 | * singular values, but only one transposition per singular vector) |
285 | 1 | pfleura2 | * |
286 | 1 | pfleura2 | DO 40 I = 1, N |
287 | 1 | pfleura2 | * |
288 | 1 | pfleura2 | * Scan for smallest D(I). |
289 | 1 | pfleura2 | * |
290 | 1 | pfleura2 | ISUB = I |
291 | 1 | pfleura2 | SMIN = D( I ) |
292 | 1 | pfleura2 | DO 30 J = I + 1, N |
293 | 1 | pfleura2 | IF( D( J ).LT.SMIN ) THEN |
294 | 1 | pfleura2 | ISUB = J |
295 | 1 | pfleura2 | SMIN = D( J ) |
296 | 1 | pfleura2 | END IF |
297 | 1 | pfleura2 | 30 CONTINUE |
298 | 1 | pfleura2 | IF( ISUB.NE.I ) THEN |
299 | 1 | pfleura2 | * |
300 | 1 | pfleura2 | * Swap singular values and vectors. |
301 | 1 | pfleura2 | * |
302 | 1 | pfleura2 | D( ISUB ) = D( I ) |
303 | 1 | pfleura2 | D( I ) = SMIN |
304 | 1 | pfleura2 | IF( NCVT.GT.0 ) |
305 | 1 | pfleura2 | $ CALL DSWAP( NCVT, VT( ISUB, 1 ), LDVT, VT( I, 1 ), LDVT ) |
306 | 1 | pfleura2 | IF( NRU.GT.0 ) |
307 | 1 | pfleura2 | $ CALL DSWAP( NRU, U( 1, ISUB ), 1, U( 1, I ), 1 ) |
308 | 1 | pfleura2 | IF( NCC.GT.0 ) |
309 | 1 | pfleura2 | $ CALL DSWAP( NCC, C( ISUB, 1 ), LDC, C( I, 1 ), LDC ) |
310 | 1 | pfleura2 | END IF |
311 | 1 | pfleura2 | 40 CONTINUE |
312 | 1 | pfleura2 | * |
313 | 1 | pfleura2 | RETURN |
314 | 1 | pfleura2 | * |
315 | 1 | pfleura2 | * End of DLASDQ |
316 | 1 | pfleura2 | * |
317 | 1 | pfleura2 | END |