root / src / lapack / double / dbdsqr.f @ 10
Historique | Voir | Annoter | Télécharger (23,46 ko)
1 | 1 | pfleura2 | SUBROUTINE DBDSQR( UPLO, N, NCVT, NRU, NCC, D, E, VT, LDVT, U, |
---|---|---|---|
2 | 1 | pfleura2 | $ LDU, C, LDC, WORK, 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 | * January 2007 |
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 |
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 | * DBDSQR computes the singular values and, optionally, the right and/or |
22 | 1 | pfleura2 | * left singular vectors from the singular value decomposition (SVD) of |
23 | 1 | pfleura2 | * a real N-by-N (upper or lower) bidiagonal matrix B using the implicit |
24 | 1 | pfleura2 | * zero-shift QR algorithm. The SVD of B has the form |
25 | 1 | pfleura2 | * |
26 | 1 | pfleura2 | * B = Q * S * P**T |
27 | 1 | pfleura2 | * |
28 | 1 | pfleura2 | * where S is the diagonal matrix of singular values, Q is an orthogonal |
29 | 1 | pfleura2 | * matrix of left singular vectors, and P is an orthogonal matrix of |
30 | 1 | pfleura2 | * right singular vectors. If left singular vectors are requested, this |
31 | 1 | pfleura2 | * subroutine actually returns U*Q instead of Q, and, if right singular |
32 | 1 | pfleura2 | * vectors are requested, this subroutine returns P**T*VT instead of |
33 | 1 | pfleura2 | * P**T, for given real input matrices U and VT. When U and VT are the |
34 | 1 | pfleura2 | * orthogonal matrices that reduce a general matrix A to bidiagonal |
35 | 1 | pfleura2 | * form: A = U*B*VT, as computed by DGEBRD, then |
36 | 1 | pfleura2 | * |
37 | 1 | pfleura2 | * A = (U*Q) * S * (P**T*VT) |
38 | 1 | pfleura2 | * |
39 | 1 | pfleura2 | * is the SVD of A. Optionally, the subroutine may also compute Q**T*C |
40 | 1 | pfleura2 | * for a given real input matrix C. |
41 | 1 | pfleura2 | * |
42 | 1 | pfleura2 | * See "Computing Small Singular Values of Bidiagonal Matrices With |
43 | 1 | pfleura2 | * Guaranteed High Relative Accuracy," by J. Demmel and W. Kahan, |
44 | 1 | pfleura2 | * LAPACK Working Note #3 (or SIAM J. Sci. Statist. Comput. vol. 11, |
45 | 1 | pfleura2 | * no. 5, pp. 873-912, Sept 1990) and |
46 | 1 | pfleura2 | * "Accurate singular values and differential qd algorithms," by |
47 | 1 | pfleura2 | * B. Parlett and V. Fernando, Technical Report CPAM-554, Mathematics |
48 | 1 | pfleura2 | * Department, University of California at Berkeley, July 1992 |
49 | 1 | pfleura2 | * for a detailed description of the algorithm. |
50 | 1 | pfleura2 | * |
51 | 1 | pfleura2 | * Arguments |
52 | 1 | pfleura2 | * ========= |
53 | 1 | pfleura2 | * |
54 | 1 | pfleura2 | * UPLO (input) CHARACTER*1 |
55 | 1 | pfleura2 | * = 'U': B is upper bidiagonal; |
56 | 1 | pfleura2 | * = 'L': B is lower bidiagonal. |
57 | 1 | pfleura2 | * |
58 | 1 | pfleura2 | * N (input) INTEGER |
59 | 1 | pfleura2 | * The order of the matrix B. N >= 0. |
60 | 1 | pfleura2 | * |
61 | 1 | pfleura2 | * NCVT (input) INTEGER |
62 | 1 | pfleura2 | * The number of columns of the matrix VT. NCVT >= 0. |
63 | 1 | pfleura2 | * |
64 | 1 | pfleura2 | * NRU (input) INTEGER |
65 | 1 | pfleura2 | * The number of rows of the matrix U. NRU >= 0. |
66 | 1 | pfleura2 | * |
67 | 1 | pfleura2 | * NCC (input) INTEGER |
68 | 1 | pfleura2 | * The number of columns of the matrix C. NCC >= 0. |
69 | 1 | pfleura2 | * |
70 | 1 | pfleura2 | * D (input/output) DOUBLE PRECISION array, dimension (N) |
71 | 1 | pfleura2 | * On entry, the n diagonal elements of the bidiagonal matrix B. |
72 | 1 | pfleura2 | * On exit, if INFO=0, the singular values of B in decreasing |
73 | 1 | pfleura2 | * order. |
74 | 1 | pfleura2 | * |
75 | 1 | pfleura2 | * E (input/output) DOUBLE PRECISION array, dimension (N-1) |
76 | 1 | pfleura2 | * On entry, the N-1 offdiagonal elements of the bidiagonal |
77 | 1 | pfleura2 | * matrix B. |
78 | 1 | pfleura2 | * On exit, if INFO = 0, E is destroyed; if INFO > 0, D and E |
79 | 1 | pfleura2 | * will contain the diagonal and superdiagonal elements of a |
80 | 1 | pfleura2 | * bidiagonal matrix orthogonally equivalent to the one given |
81 | 1 | pfleura2 | * as input. |
82 | 1 | pfleura2 | * |
83 | 1 | pfleura2 | * VT (input/output) DOUBLE PRECISION array, dimension (LDVT, NCVT) |
84 | 1 | pfleura2 | * On entry, an N-by-NCVT matrix VT. |
85 | 1 | pfleura2 | * On exit, VT is overwritten by P**T * VT. |
86 | 1 | pfleura2 | * Not referenced if NCVT = 0. |
87 | 1 | pfleura2 | * |
88 | 1 | pfleura2 | * LDVT (input) INTEGER |
89 | 1 | pfleura2 | * The leading dimension of the array VT. |
90 | 1 | pfleura2 | * LDVT >= max(1,N) if NCVT > 0; LDVT >= 1 if NCVT = 0. |
91 | 1 | pfleura2 | * |
92 | 1 | pfleura2 | * U (input/output) DOUBLE PRECISION array, dimension (LDU, N) |
93 | 1 | pfleura2 | * On entry, an NRU-by-N matrix U. |
94 | 1 | pfleura2 | * On exit, U is overwritten by U * Q. |
95 | 1 | pfleura2 | * Not referenced if NRU = 0. |
96 | 1 | pfleura2 | * |
97 | 1 | pfleura2 | * LDU (input) INTEGER |
98 | 1 | pfleura2 | * The leading dimension of the array U. LDU >= max(1,NRU). |
99 | 1 | pfleura2 | * |
100 | 1 | pfleura2 | * C (input/output) DOUBLE PRECISION array, dimension (LDC, NCC) |
101 | 1 | pfleura2 | * On entry, an N-by-NCC matrix C. |
102 | 1 | pfleura2 | * On exit, C is overwritten by Q**T * C. |
103 | 1 | pfleura2 | * Not referenced if NCC = 0. |
104 | 1 | pfleura2 | * |
105 | 1 | pfleura2 | * LDC (input) INTEGER |
106 | 1 | pfleura2 | * The leading dimension of the array C. |
107 | 1 | pfleura2 | * LDC >= max(1,N) if NCC > 0; LDC >=1 if NCC = 0. |
108 | 1 | pfleura2 | * |
109 | 1 | pfleura2 | * WORK (workspace) DOUBLE PRECISION array, dimension (4*N) |
110 | 1 | pfleura2 | * |
111 | 1 | pfleura2 | * INFO (output) INTEGER |
112 | 1 | pfleura2 | * = 0: successful exit |
113 | 1 | pfleura2 | * < 0: If INFO = -i, the i-th argument had an illegal value |
114 | 1 | pfleura2 | * > 0: |
115 | 1 | pfleura2 | * if NCVT = NRU = NCC = 0, |
116 | 1 | pfleura2 | * = 1, a split was marked by a positive value in E |
117 | 1 | pfleura2 | * = 2, current block of Z not diagonalized after 30*N |
118 | 1 | pfleura2 | * iterations (in inner while loop) |
119 | 1 | pfleura2 | * = 3, termination criterion of outer while loop not met |
120 | 1 | pfleura2 | * (program created more than N unreduced blocks) |
121 | 1 | pfleura2 | * else NCVT = NRU = NCC = 0, |
122 | 1 | pfleura2 | * the algorithm did not converge; D and E contain the |
123 | 1 | pfleura2 | * elements of a bidiagonal matrix which is orthogonally |
124 | 1 | pfleura2 | * similar to the input matrix B; if INFO = i, i |
125 | 1 | pfleura2 | * elements of E have not converged to zero. |
126 | 1 | pfleura2 | * |
127 | 1 | pfleura2 | * Internal Parameters |
128 | 1 | pfleura2 | * =================== |
129 | 1 | pfleura2 | * |
130 | 1 | pfleura2 | * TOLMUL DOUBLE PRECISION, default = max(10,min(100,EPS**(-1/8))) |
131 | 1 | pfleura2 | * TOLMUL controls the convergence criterion of the QR loop. |
132 | 1 | pfleura2 | * If it is positive, TOLMUL*EPS is the desired relative |
133 | 1 | pfleura2 | * precision in the computed singular values. |
134 | 1 | pfleura2 | * If it is negative, abs(TOLMUL*EPS*sigma_max) is the |
135 | 1 | pfleura2 | * desired absolute accuracy in the computed singular |
136 | 1 | pfleura2 | * values (corresponds to relative accuracy |
137 | 1 | pfleura2 | * abs(TOLMUL*EPS) in the largest singular value. |
138 | 1 | pfleura2 | * abs(TOLMUL) should be between 1 and 1/EPS, and preferably |
139 | 1 | pfleura2 | * between 10 (for fast convergence) and .1/EPS |
140 | 1 | pfleura2 | * (for there to be some accuracy in the results). |
141 | 1 | pfleura2 | * Default is to lose at either one eighth or 2 of the |
142 | 1 | pfleura2 | * available decimal digits in each computed singular value |
143 | 1 | pfleura2 | * (whichever is smaller). |
144 | 1 | pfleura2 | * |
145 | 1 | pfleura2 | * MAXITR INTEGER, default = 6 |
146 | 1 | pfleura2 | * MAXITR controls the maximum number of passes of the |
147 | 1 | pfleura2 | * algorithm through its inner loop. The algorithms stops |
148 | 1 | pfleura2 | * (and so fails to converge) if the number of passes |
149 | 1 | pfleura2 | * through the inner loop exceeds MAXITR*N**2. |
150 | 1 | pfleura2 | * |
151 | 1 | pfleura2 | * ===================================================================== |
152 | 1 | pfleura2 | * |
153 | 1 | pfleura2 | * .. Parameters .. |
154 | 1 | pfleura2 | DOUBLE PRECISION ZERO |
155 | 1 | pfleura2 | PARAMETER ( ZERO = 0.0D0 ) |
156 | 1 | pfleura2 | DOUBLE PRECISION ONE |
157 | 1 | pfleura2 | PARAMETER ( ONE = 1.0D0 ) |
158 | 1 | pfleura2 | DOUBLE PRECISION NEGONE |
159 | 1 | pfleura2 | PARAMETER ( NEGONE = -1.0D0 ) |
160 | 1 | pfleura2 | DOUBLE PRECISION HNDRTH |
161 | 1 | pfleura2 | PARAMETER ( HNDRTH = 0.01D0 ) |
162 | 1 | pfleura2 | DOUBLE PRECISION TEN |
163 | 1 | pfleura2 | PARAMETER ( TEN = 10.0D0 ) |
164 | 1 | pfleura2 | DOUBLE PRECISION HNDRD |
165 | 1 | pfleura2 | PARAMETER ( HNDRD = 100.0D0 ) |
166 | 1 | pfleura2 | DOUBLE PRECISION MEIGTH |
167 | 1 | pfleura2 | PARAMETER ( MEIGTH = -0.125D0 ) |
168 | 1 | pfleura2 | INTEGER MAXITR |
169 | 1 | pfleura2 | PARAMETER ( MAXITR = 6 ) |
170 | 1 | pfleura2 | * .. |
171 | 1 | pfleura2 | * .. Local Scalars .. |
172 | 1 | pfleura2 | LOGICAL LOWER, ROTATE |
173 | 1 | pfleura2 | INTEGER I, IDIR, ISUB, ITER, J, LL, LLL, M, MAXIT, NM1, |
174 | 1 | pfleura2 | $ NM12, NM13, OLDLL, OLDM |
175 | 1 | pfleura2 | DOUBLE PRECISION ABSE, ABSS, COSL, COSR, CS, EPS, F, G, H, MU, |
176 | 1 | pfleura2 | $ OLDCS, OLDSN, R, SHIFT, SIGMN, SIGMX, SINL, |
177 | 1 | pfleura2 | $ SINR, SLL, SMAX, SMIN, SMINL, SMINOA, |
178 | 1 | pfleura2 | $ SN, THRESH, TOL, TOLMUL, UNFL |
179 | 1 | pfleura2 | * .. |
180 | 1 | pfleura2 | * .. External Functions .. |
181 | 1 | pfleura2 | LOGICAL LSAME |
182 | 1 | pfleura2 | DOUBLE PRECISION DLAMCH |
183 | 1 | pfleura2 | EXTERNAL LSAME, DLAMCH |
184 | 1 | pfleura2 | * .. |
185 | 1 | pfleura2 | * .. External Subroutines .. |
186 | 1 | pfleura2 | EXTERNAL DLARTG, DLAS2, DLASQ1, DLASR, DLASV2, DROT, |
187 | 1 | pfleura2 | $ DSCAL, DSWAP, XERBLA |
188 | 1 | pfleura2 | * .. |
189 | 1 | pfleura2 | * .. Intrinsic Functions .. |
190 | 1 | pfleura2 | INTRINSIC ABS, DBLE, MAX, MIN, SIGN, SQRT |
191 | 1 | pfleura2 | * .. |
192 | 1 | pfleura2 | * .. Executable Statements .. |
193 | 1 | pfleura2 | * |
194 | 1 | pfleura2 | * Test the input parameters. |
195 | 1 | pfleura2 | * |
196 | 1 | pfleura2 | INFO = 0 |
197 | 1 | pfleura2 | LOWER = LSAME( UPLO, 'L' ) |
198 | 1 | pfleura2 | IF( .NOT.LSAME( UPLO, 'U' ) .AND. .NOT.LOWER ) THEN |
199 | 1 | pfleura2 | INFO = -1 |
200 | 1 | pfleura2 | ELSE IF( N.LT.0 ) THEN |
201 | 1 | pfleura2 | INFO = -2 |
202 | 1 | pfleura2 | ELSE IF( NCVT.LT.0 ) THEN |
203 | 1 | pfleura2 | INFO = -3 |
204 | 1 | pfleura2 | ELSE IF( NRU.LT.0 ) THEN |
205 | 1 | pfleura2 | INFO = -4 |
206 | 1 | pfleura2 | ELSE IF( NCC.LT.0 ) THEN |
207 | 1 | pfleura2 | INFO = -5 |
208 | 1 | pfleura2 | ELSE IF( ( NCVT.EQ.0 .AND. LDVT.LT.1 ) .OR. |
209 | 1 | pfleura2 | $ ( NCVT.GT.0 .AND. LDVT.LT.MAX( 1, N ) ) ) THEN |
210 | 1 | pfleura2 | INFO = -9 |
211 | 1 | pfleura2 | ELSE IF( LDU.LT.MAX( 1, NRU ) ) THEN |
212 | 1 | pfleura2 | INFO = -11 |
213 | 1 | pfleura2 | ELSE IF( ( NCC.EQ.0 .AND. LDC.LT.1 ) .OR. |
214 | 1 | pfleura2 | $ ( NCC.GT.0 .AND. LDC.LT.MAX( 1, N ) ) ) THEN |
215 | 1 | pfleura2 | INFO = -13 |
216 | 1 | pfleura2 | END IF |
217 | 1 | pfleura2 | IF( INFO.NE.0 ) THEN |
218 | 1 | pfleura2 | CALL XERBLA( 'DBDSQR', -INFO ) |
219 | 1 | pfleura2 | RETURN |
220 | 1 | pfleura2 | END IF |
221 | 1 | pfleura2 | IF( N.EQ.0 ) |
222 | 1 | pfleura2 | $ RETURN |
223 | 1 | pfleura2 | IF( N.EQ.1 ) |
224 | 1 | pfleura2 | $ GO TO 160 |
225 | 1 | pfleura2 | * |
226 | 1 | pfleura2 | * ROTATE is true if any singular vectors desired, false otherwise |
227 | 1 | pfleura2 | * |
228 | 1 | pfleura2 | ROTATE = ( NCVT.GT.0 ) .OR. ( NRU.GT.0 ) .OR. ( NCC.GT.0 ) |
229 | 1 | pfleura2 | * |
230 | 1 | pfleura2 | * If no singular vectors desired, use qd algorithm |
231 | 1 | pfleura2 | * |
232 | 1 | pfleura2 | IF( .NOT.ROTATE ) THEN |
233 | 1 | pfleura2 | CALL DLASQ1( N, D, E, WORK, INFO ) |
234 | 1 | pfleura2 | RETURN |
235 | 1 | pfleura2 | END IF |
236 | 1 | pfleura2 | * |
237 | 1 | pfleura2 | NM1 = N - 1 |
238 | 1 | pfleura2 | NM12 = NM1 + NM1 |
239 | 1 | pfleura2 | NM13 = NM12 + NM1 |
240 | 1 | pfleura2 | IDIR = 0 |
241 | 1 | pfleura2 | * |
242 | 1 | pfleura2 | * Get machine constants |
243 | 1 | pfleura2 | * |
244 | 1 | pfleura2 | EPS = DLAMCH( 'Epsilon' ) |
245 | 1 | pfleura2 | UNFL = DLAMCH( 'Safe minimum' ) |
246 | 1 | pfleura2 | * |
247 | 1 | pfleura2 | * If matrix lower bidiagonal, rotate to be upper bidiagonal |
248 | 1 | pfleura2 | * by applying Givens rotations on the left |
249 | 1 | pfleura2 | * |
250 | 1 | pfleura2 | IF( LOWER ) THEN |
251 | 1 | pfleura2 | DO 10 I = 1, N - 1 |
252 | 1 | pfleura2 | CALL DLARTG( D( I ), E( I ), CS, SN, R ) |
253 | 1 | pfleura2 | D( I ) = R |
254 | 1 | pfleura2 | E( I ) = SN*D( I+1 ) |
255 | 1 | pfleura2 | D( I+1 ) = CS*D( I+1 ) |
256 | 1 | pfleura2 | WORK( I ) = CS |
257 | 1 | pfleura2 | WORK( NM1+I ) = SN |
258 | 1 | pfleura2 | 10 CONTINUE |
259 | 1 | pfleura2 | * |
260 | 1 | pfleura2 | * Update singular vectors if desired |
261 | 1 | pfleura2 | * |
262 | 1 | pfleura2 | IF( NRU.GT.0 ) |
263 | 1 | pfleura2 | $ CALL DLASR( 'R', 'V', 'F', NRU, N, WORK( 1 ), WORK( N ), U, |
264 | 1 | pfleura2 | $ LDU ) |
265 | 1 | pfleura2 | IF( NCC.GT.0 ) |
266 | 1 | pfleura2 | $ CALL DLASR( 'L', 'V', 'F', N, NCC, WORK( 1 ), WORK( N ), C, |
267 | 1 | pfleura2 | $ LDC ) |
268 | 1 | pfleura2 | END IF |
269 | 1 | pfleura2 | * |
270 | 1 | pfleura2 | * Compute singular values to relative accuracy TOL |
271 | 1 | pfleura2 | * (By setting TOL to be negative, algorithm will compute |
272 | 1 | pfleura2 | * singular values to absolute accuracy ABS(TOL)*norm(input matrix)) |
273 | 1 | pfleura2 | * |
274 | 1 | pfleura2 | TOLMUL = MAX( TEN, MIN( HNDRD, EPS**MEIGTH ) ) |
275 | 1 | pfleura2 | TOL = TOLMUL*EPS |
276 | 1 | pfleura2 | * |
277 | 1 | pfleura2 | * Compute approximate maximum, minimum singular values |
278 | 1 | pfleura2 | * |
279 | 1 | pfleura2 | SMAX = ZERO |
280 | 1 | pfleura2 | DO 20 I = 1, N |
281 | 1 | pfleura2 | SMAX = MAX( SMAX, ABS( D( I ) ) ) |
282 | 1 | pfleura2 | 20 CONTINUE |
283 | 1 | pfleura2 | DO 30 I = 1, N - 1 |
284 | 1 | pfleura2 | SMAX = MAX( SMAX, ABS( E( I ) ) ) |
285 | 1 | pfleura2 | 30 CONTINUE |
286 | 1 | pfleura2 | SMINL = ZERO |
287 | 1 | pfleura2 | IF( TOL.GE.ZERO ) THEN |
288 | 1 | pfleura2 | * |
289 | 1 | pfleura2 | * Relative accuracy desired |
290 | 1 | pfleura2 | * |
291 | 1 | pfleura2 | SMINOA = ABS( D( 1 ) ) |
292 | 1 | pfleura2 | IF( SMINOA.EQ.ZERO ) |
293 | 1 | pfleura2 | $ GO TO 50 |
294 | 1 | pfleura2 | MU = SMINOA |
295 | 1 | pfleura2 | DO 40 I = 2, N |
296 | 1 | pfleura2 | MU = ABS( D( I ) )*( MU / ( MU+ABS( E( I-1 ) ) ) ) |
297 | 1 | pfleura2 | SMINOA = MIN( SMINOA, MU ) |
298 | 1 | pfleura2 | IF( SMINOA.EQ.ZERO ) |
299 | 1 | pfleura2 | $ GO TO 50 |
300 | 1 | pfleura2 | 40 CONTINUE |
301 | 1 | pfleura2 | 50 CONTINUE |
302 | 1 | pfleura2 | SMINOA = SMINOA / SQRT( DBLE( N ) ) |
303 | 1 | pfleura2 | THRESH = MAX( TOL*SMINOA, MAXITR*N*N*UNFL ) |
304 | 1 | pfleura2 | ELSE |
305 | 1 | pfleura2 | * |
306 | 1 | pfleura2 | * Absolute accuracy desired |
307 | 1 | pfleura2 | * |
308 | 1 | pfleura2 | THRESH = MAX( ABS( TOL )*SMAX, MAXITR*N*N*UNFL ) |
309 | 1 | pfleura2 | END IF |
310 | 1 | pfleura2 | * |
311 | 1 | pfleura2 | * Prepare for main iteration loop for the singular values |
312 | 1 | pfleura2 | * (MAXIT is the maximum number of passes through the inner |
313 | 1 | pfleura2 | * loop permitted before nonconvergence signalled.) |
314 | 1 | pfleura2 | * |
315 | 1 | pfleura2 | MAXIT = MAXITR*N*N |
316 | 1 | pfleura2 | ITER = 0 |
317 | 1 | pfleura2 | OLDLL = -1 |
318 | 1 | pfleura2 | OLDM = -1 |
319 | 1 | pfleura2 | * |
320 | 1 | pfleura2 | * M points to last element of unconverged part of matrix |
321 | 1 | pfleura2 | * |
322 | 1 | pfleura2 | M = N |
323 | 1 | pfleura2 | * |
324 | 1 | pfleura2 | * Begin main iteration loop |
325 | 1 | pfleura2 | * |
326 | 1 | pfleura2 | 60 CONTINUE |
327 | 1 | pfleura2 | * |
328 | 1 | pfleura2 | * Check for convergence or exceeding iteration count |
329 | 1 | pfleura2 | * |
330 | 1 | pfleura2 | IF( M.LE.1 ) |
331 | 1 | pfleura2 | $ GO TO 160 |
332 | 1 | pfleura2 | IF( ITER.GT.MAXIT ) |
333 | 1 | pfleura2 | $ GO TO 200 |
334 | 1 | pfleura2 | * |
335 | 1 | pfleura2 | * Find diagonal block of matrix to work on |
336 | 1 | pfleura2 | * |
337 | 1 | pfleura2 | IF( TOL.LT.ZERO .AND. ABS( D( M ) ).LE.THRESH ) |
338 | 1 | pfleura2 | $ D( M ) = ZERO |
339 | 1 | pfleura2 | SMAX = ABS( D( M ) ) |
340 | 1 | pfleura2 | SMIN = SMAX |
341 | 1 | pfleura2 | DO 70 LLL = 1, M - 1 |
342 | 1 | pfleura2 | LL = M - LLL |
343 | 1 | pfleura2 | ABSS = ABS( D( LL ) ) |
344 | 1 | pfleura2 | ABSE = ABS( E( LL ) ) |
345 | 1 | pfleura2 | IF( TOL.LT.ZERO .AND. ABSS.LE.THRESH ) |
346 | 1 | pfleura2 | $ D( LL ) = ZERO |
347 | 1 | pfleura2 | IF( ABSE.LE.THRESH ) |
348 | 1 | pfleura2 | $ GO TO 80 |
349 | 1 | pfleura2 | SMIN = MIN( SMIN, ABSS ) |
350 | 1 | pfleura2 | SMAX = MAX( SMAX, ABSS, ABSE ) |
351 | 1 | pfleura2 | 70 CONTINUE |
352 | 1 | pfleura2 | LL = 0 |
353 | 1 | pfleura2 | GO TO 90 |
354 | 1 | pfleura2 | 80 CONTINUE |
355 | 1 | pfleura2 | E( LL ) = ZERO |
356 | 1 | pfleura2 | * |
357 | 1 | pfleura2 | * Matrix splits since E(LL) = 0 |
358 | 1 | pfleura2 | * |
359 | 1 | pfleura2 | IF( LL.EQ.M-1 ) THEN |
360 | 1 | pfleura2 | * |
361 | 1 | pfleura2 | * Convergence of bottom singular value, return to top of loop |
362 | 1 | pfleura2 | * |
363 | 1 | pfleura2 | M = M - 1 |
364 | 1 | pfleura2 | GO TO 60 |
365 | 1 | pfleura2 | END IF |
366 | 1 | pfleura2 | 90 CONTINUE |
367 | 1 | pfleura2 | LL = LL + 1 |
368 | 1 | pfleura2 | * |
369 | 1 | pfleura2 | * E(LL) through E(M-1) are nonzero, E(LL-1) is zero |
370 | 1 | pfleura2 | * |
371 | 1 | pfleura2 | IF( LL.EQ.M-1 ) THEN |
372 | 1 | pfleura2 | * |
373 | 1 | pfleura2 | * 2 by 2 block, handle separately |
374 | 1 | pfleura2 | * |
375 | 1 | pfleura2 | CALL DLASV2( D( M-1 ), E( M-1 ), D( M ), SIGMN, SIGMX, SINR, |
376 | 1 | pfleura2 | $ COSR, SINL, COSL ) |
377 | 1 | pfleura2 | D( M-1 ) = SIGMX |
378 | 1 | pfleura2 | E( M-1 ) = ZERO |
379 | 1 | pfleura2 | D( M ) = SIGMN |
380 | 1 | pfleura2 | * |
381 | 1 | pfleura2 | * Compute singular vectors, if desired |
382 | 1 | pfleura2 | * |
383 | 1 | pfleura2 | IF( NCVT.GT.0 ) |
384 | 1 | pfleura2 | $ CALL DROT( NCVT, VT( M-1, 1 ), LDVT, VT( M, 1 ), LDVT, COSR, |
385 | 1 | pfleura2 | $ SINR ) |
386 | 1 | pfleura2 | IF( NRU.GT.0 ) |
387 | 1 | pfleura2 | $ CALL DROT( NRU, U( 1, M-1 ), 1, U( 1, M ), 1, COSL, SINL ) |
388 | 1 | pfleura2 | IF( NCC.GT.0 ) |
389 | 1 | pfleura2 | $ CALL DROT( NCC, C( M-1, 1 ), LDC, C( M, 1 ), LDC, COSL, |
390 | 1 | pfleura2 | $ SINL ) |
391 | 1 | pfleura2 | M = M - 2 |
392 | 1 | pfleura2 | GO TO 60 |
393 | 1 | pfleura2 | END IF |
394 | 1 | pfleura2 | * |
395 | 1 | pfleura2 | * If working on new submatrix, choose shift direction |
396 | 1 | pfleura2 | * (from larger end diagonal element towards smaller) |
397 | 1 | pfleura2 | * |
398 | 1 | pfleura2 | IF( LL.GT.OLDM .OR. M.LT.OLDLL ) THEN |
399 | 1 | pfleura2 | IF( ABS( D( LL ) ).GE.ABS( D( M ) ) ) THEN |
400 | 1 | pfleura2 | * |
401 | 1 | pfleura2 | * Chase bulge from top (big end) to bottom (small end) |
402 | 1 | pfleura2 | * |
403 | 1 | pfleura2 | IDIR = 1 |
404 | 1 | pfleura2 | ELSE |
405 | 1 | pfleura2 | * |
406 | 1 | pfleura2 | * Chase bulge from bottom (big end) to top (small end) |
407 | 1 | pfleura2 | * |
408 | 1 | pfleura2 | IDIR = 2 |
409 | 1 | pfleura2 | END IF |
410 | 1 | pfleura2 | END IF |
411 | 1 | pfleura2 | * |
412 | 1 | pfleura2 | * Apply convergence tests |
413 | 1 | pfleura2 | * |
414 | 1 | pfleura2 | IF( IDIR.EQ.1 ) THEN |
415 | 1 | pfleura2 | * |
416 | 1 | pfleura2 | * Run convergence test in forward direction |
417 | 1 | pfleura2 | * First apply standard test to bottom of matrix |
418 | 1 | pfleura2 | * |
419 | 1 | pfleura2 | IF( ABS( E( M-1 ) ).LE.ABS( TOL )*ABS( D( M ) ) .OR. |
420 | 1 | pfleura2 | $ ( TOL.LT.ZERO .AND. ABS( E( M-1 ) ).LE.THRESH ) ) THEN |
421 | 1 | pfleura2 | E( M-1 ) = ZERO |
422 | 1 | pfleura2 | GO TO 60 |
423 | 1 | pfleura2 | END IF |
424 | 1 | pfleura2 | * |
425 | 1 | pfleura2 | IF( TOL.GE.ZERO ) THEN |
426 | 1 | pfleura2 | * |
427 | 1 | pfleura2 | * If relative accuracy desired, |
428 | 1 | pfleura2 | * apply convergence criterion forward |
429 | 1 | pfleura2 | * |
430 | 1 | pfleura2 | MU = ABS( D( LL ) ) |
431 | 1 | pfleura2 | SMINL = MU |
432 | 1 | pfleura2 | DO 100 LLL = LL, M - 1 |
433 | 1 | pfleura2 | IF( ABS( E( LLL ) ).LE.TOL*MU ) THEN |
434 | 1 | pfleura2 | E( LLL ) = ZERO |
435 | 1 | pfleura2 | GO TO 60 |
436 | 1 | pfleura2 | END IF |
437 | 1 | pfleura2 | MU = ABS( D( LLL+1 ) )*( MU / ( MU+ABS( E( LLL ) ) ) ) |
438 | 1 | pfleura2 | SMINL = MIN( SMINL, MU ) |
439 | 1 | pfleura2 | 100 CONTINUE |
440 | 1 | pfleura2 | END IF |
441 | 1 | pfleura2 | * |
442 | 1 | pfleura2 | ELSE |
443 | 1 | pfleura2 | * |
444 | 1 | pfleura2 | * Run convergence test in backward direction |
445 | 1 | pfleura2 | * First apply standard test to top of matrix |
446 | 1 | pfleura2 | * |
447 | 1 | pfleura2 | IF( ABS( E( LL ) ).LE.ABS( TOL )*ABS( D( LL ) ) .OR. |
448 | 1 | pfleura2 | $ ( TOL.LT.ZERO .AND. ABS( E( LL ) ).LE.THRESH ) ) THEN |
449 | 1 | pfleura2 | E( LL ) = ZERO |
450 | 1 | pfleura2 | GO TO 60 |
451 | 1 | pfleura2 | END IF |
452 | 1 | pfleura2 | * |
453 | 1 | pfleura2 | IF( TOL.GE.ZERO ) THEN |
454 | 1 | pfleura2 | * |
455 | 1 | pfleura2 | * If relative accuracy desired, |
456 | 1 | pfleura2 | * apply convergence criterion backward |
457 | 1 | pfleura2 | * |
458 | 1 | pfleura2 | MU = ABS( D( M ) ) |
459 | 1 | pfleura2 | SMINL = MU |
460 | 1 | pfleura2 | DO 110 LLL = M - 1, LL, -1 |
461 | 1 | pfleura2 | IF( ABS( E( LLL ) ).LE.TOL*MU ) THEN |
462 | 1 | pfleura2 | E( LLL ) = ZERO |
463 | 1 | pfleura2 | GO TO 60 |
464 | 1 | pfleura2 | END IF |
465 | 1 | pfleura2 | MU = ABS( D( LLL ) )*( MU / ( MU+ABS( E( LLL ) ) ) ) |
466 | 1 | pfleura2 | SMINL = MIN( SMINL, MU ) |
467 | 1 | pfleura2 | 110 CONTINUE |
468 | 1 | pfleura2 | END IF |
469 | 1 | pfleura2 | END IF |
470 | 1 | pfleura2 | OLDLL = LL |
471 | 1 | pfleura2 | OLDM = M |
472 | 1 | pfleura2 | * |
473 | 1 | pfleura2 | * Compute shift. First, test if shifting would ruin relative |
474 | 1 | pfleura2 | * accuracy, and if so set the shift to zero. |
475 | 1 | pfleura2 | * |
476 | 1 | pfleura2 | IF( TOL.GE.ZERO .AND. N*TOL*( SMINL / SMAX ).LE. |
477 | 1 | pfleura2 | $ MAX( EPS, HNDRTH*TOL ) ) THEN |
478 | 1 | pfleura2 | * |
479 | 1 | pfleura2 | * Use a zero shift to avoid loss of relative accuracy |
480 | 1 | pfleura2 | * |
481 | 1 | pfleura2 | SHIFT = ZERO |
482 | 1 | pfleura2 | ELSE |
483 | 1 | pfleura2 | * |
484 | 1 | pfleura2 | * Compute the shift from 2-by-2 block at end of matrix |
485 | 1 | pfleura2 | * |
486 | 1 | pfleura2 | IF( IDIR.EQ.1 ) THEN |
487 | 1 | pfleura2 | SLL = ABS( D( LL ) ) |
488 | 1 | pfleura2 | CALL DLAS2( D( M-1 ), E( M-1 ), D( M ), SHIFT, R ) |
489 | 1 | pfleura2 | ELSE |
490 | 1 | pfleura2 | SLL = ABS( D( M ) ) |
491 | 1 | pfleura2 | CALL DLAS2( D( LL ), E( LL ), D( LL+1 ), SHIFT, R ) |
492 | 1 | pfleura2 | END IF |
493 | 1 | pfleura2 | * |
494 | 1 | pfleura2 | * Test if shift negligible, and if so set to zero |
495 | 1 | pfleura2 | * |
496 | 1 | pfleura2 | IF( SLL.GT.ZERO ) THEN |
497 | 1 | pfleura2 | IF( ( SHIFT / SLL )**2.LT.EPS ) |
498 | 1 | pfleura2 | $ SHIFT = ZERO |
499 | 1 | pfleura2 | END IF |
500 | 1 | pfleura2 | END IF |
501 | 1 | pfleura2 | * |
502 | 1 | pfleura2 | * Increment iteration count |
503 | 1 | pfleura2 | * |
504 | 1 | pfleura2 | ITER = ITER + M - LL |
505 | 1 | pfleura2 | * |
506 | 1 | pfleura2 | * If SHIFT = 0, do simplified QR iteration |
507 | 1 | pfleura2 | * |
508 | 1 | pfleura2 | IF( SHIFT.EQ.ZERO ) THEN |
509 | 1 | pfleura2 | IF( IDIR.EQ.1 ) THEN |
510 | 1 | pfleura2 | * |
511 | 1 | pfleura2 | * Chase bulge from top to bottom |
512 | 1 | pfleura2 | * Save cosines and sines for later singular vector updates |
513 | 1 | pfleura2 | * |
514 | 1 | pfleura2 | CS = ONE |
515 | 1 | pfleura2 | OLDCS = ONE |
516 | 1 | pfleura2 | DO 120 I = LL, M - 1 |
517 | 1 | pfleura2 | CALL DLARTG( D( I )*CS, E( I ), CS, SN, R ) |
518 | 1 | pfleura2 | IF( I.GT.LL ) |
519 | 1 | pfleura2 | $ E( I-1 ) = OLDSN*R |
520 | 1 | pfleura2 | CALL DLARTG( OLDCS*R, D( I+1 )*SN, OLDCS, OLDSN, D( I ) ) |
521 | 1 | pfleura2 | WORK( I-LL+1 ) = CS |
522 | 1 | pfleura2 | WORK( I-LL+1+NM1 ) = SN |
523 | 1 | pfleura2 | WORK( I-LL+1+NM12 ) = OLDCS |
524 | 1 | pfleura2 | WORK( I-LL+1+NM13 ) = OLDSN |
525 | 1 | pfleura2 | 120 CONTINUE |
526 | 1 | pfleura2 | H = D( M )*CS |
527 | 1 | pfleura2 | D( M ) = H*OLDCS |
528 | 1 | pfleura2 | E( M-1 ) = H*OLDSN |
529 | 1 | pfleura2 | * |
530 | 1 | pfleura2 | * Update singular vectors |
531 | 1 | pfleura2 | * |
532 | 1 | pfleura2 | IF( NCVT.GT.0 ) |
533 | 1 | pfleura2 | $ CALL DLASR( 'L', 'V', 'F', M-LL+1, NCVT, WORK( 1 ), |
534 | 1 | pfleura2 | $ WORK( N ), VT( LL, 1 ), LDVT ) |
535 | 1 | pfleura2 | IF( NRU.GT.0 ) |
536 | 1 | pfleura2 | $ CALL DLASR( 'R', 'V', 'F', NRU, M-LL+1, WORK( NM12+1 ), |
537 | 1 | pfleura2 | $ WORK( NM13+1 ), U( 1, LL ), LDU ) |
538 | 1 | pfleura2 | IF( NCC.GT.0 ) |
539 | 1 | pfleura2 | $ CALL DLASR( 'L', 'V', 'F', M-LL+1, NCC, WORK( NM12+1 ), |
540 | 1 | pfleura2 | $ WORK( NM13+1 ), C( LL, 1 ), LDC ) |
541 | 1 | pfleura2 | * |
542 | 1 | pfleura2 | * Test convergence |
543 | 1 | pfleura2 | * |
544 | 1 | pfleura2 | IF( ABS( E( M-1 ) ).LE.THRESH ) |
545 | 1 | pfleura2 | $ E( M-1 ) = ZERO |
546 | 1 | pfleura2 | * |
547 | 1 | pfleura2 | ELSE |
548 | 1 | pfleura2 | * |
549 | 1 | pfleura2 | * Chase bulge from bottom to top |
550 | 1 | pfleura2 | * Save cosines and sines for later singular vector updates |
551 | 1 | pfleura2 | * |
552 | 1 | pfleura2 | CS = ONE |
553 | 1 | pfleura2 | OLDCS = ONE |
554 | 1 | pfleura2 | DO 130 I = M, LL + 1, -1 |
555 | 1 | pfleura2 | CALL DLARTG( D( I )*CS, E( I-1 ), CS, SN, R ) |
556 | 1 | pfleura2 | IF( I.LT.M ) |
557 | 1 | pfleura2 | $ E( I ) = OLDSN*R |
558 | 1 | pfleura2 | CALL DLARTG( OLDCS*R, D( I-1 )*SN, OLDCS, OLDSN, D( I ) ) |
559 | 1 | pfleura2 | WORK( I-LL ) = CS |
560 | 1 | pfleura2 | WORK( I-LL+NM1 ) = -SN |
561 | 1 | pfleura2 | WORK( I-LL+NM12 ) = OLDCS |
562 | 1 | pfleura2 | WORK( I-LL+NM13 ) = -OLDSN |
563 | 1 | pfleura2 | 130 CONTINUE |
564 | 1 | pfleura2 | H = D( LL )*CS |
565 | 1 | pfleura2 | D( LL ) = H*OLDCS |
566 | 1 | pfleura2 | E( LL ) = H*OLDSN |
567 | 1 | pfleura2 | * |
568 | 1 | pfleura2 | * Update singular vectors |
569 | 1 | pfleura2 | * |
570 | 1 | pfleura2 | IF( NCVT.GT.0 ) |
571 | 1 | pfleura2 | $ CALL DLASR( 'L', 'V', 'B', M-LL+1, NCVT, WORK( NM12+1 ), |
572 | 1 | pfleura2 | $ WORK( NM13+1 ), VT( LL, 1 ), LDVT ) |
573 | 1 | pfleura2 | IF( NRU.GT.0 ) |
574 | 1 | pfleura2 | $ CALL DLASR( 'R', 'V', 'B', NRU, M-LL+1, WORK( 1 ), |
575 | 1 | pfleura2 | $ WORK( N ), U( 1, LL ), LDU ) |
576 | 1 | pfleura2 | IF( NCC.GT.0 ) |
577 | 1 | pfleura2 | $ CALL DLASR( 'L', 'V', 'B', M-LL+1, NCC, WORK( 1 ), |
578 | 1 | pfleura2 | $ WORK( N ), C( LL, 1 ), LDC ) |
579 | 1 | pfleura2 | * |
580 | 1 | pfleura2 | * Test convergence |
581 | 1 | pfleura2 | * |
582 | 1 | pfleura2 | IF( ABS( E( LL ) ).LE.THRESH ) |
583 | 1 | pfleura2 | $ E( LL ) = ZERO |
584 | 1 | pfleura2 | END IF |
585 | 1 | pfleura2 | ELSE |
586 | 1 | pfleura2 | * |
587 | 1 | pfleura2 | * Use nonzero shift |
588 | 1 | pfleura2 | * |
589 | 1 | pfleura2 | IF( IDIR.EQ.1 ) THEN |
590 | 1 | pfleura2 | * |
591 | 1 | pfleura2 | * Chase bulge from top to bottom |
592 | 1 | pfleura2 | * Save cosines and sines for later singular vector updates |
593 | 1 | pfleura2 | * |
594 | 1 | pfleura2 | F = ( ABS( D( LL ) )-SHIFT )* |
595 | 1 | pfleura2 | $ ( SIGN( ONE, D( LL ) )+SHIFT / D( LL ) ) |
596 | 1 | pfleura2 | G = E( LL ) |
597 | 1 | pfleura2 | DO 140 I = LL, M - 1 |
598 | 1 | pfleura2 | CALL DLARTG( F, G, COSR, SINR, R ) |
599 | 1 | pfleura2 | IF( I.GT.LL ) |
600 | 1 | pfleura2 | $ E( I-1 ) = R |
601 | 1 | pfleura2 | F = COSR*D( I ) + SINR*E( I ) |
602 | 1 | pfleura2 | E( I ) = COSR*E( I ) - SINR*D( I ) |
603 | 1 | pfleura2 | G = SINR*D( I+1 ) |
604 | 1 | pfleura2 | D( I+1 ) = COSR*D( I+1 ) |
605 | 1 | pfleura2 | CALL DLARTG( F, G, COSL, SINL, R ) |
606 | 1 | pfleura2 | D( I ) = R |
607 | 1 | pfleura2 | F = COSL*E( I ) + SINL*D( I+1 ) |
608 | 1 | pfleura2 | D( I+1 ) = COSL*D( I+1 ) - SINL*E( I ) |
609 | 1 | pfleura2 | IF( I.LT.M-1 ) THEN |
610 | 1 | pfleura2 | G = SINL*E( I+1 ) |
611 | 1 | pfleura2 | E( I+1 ) = COSL*E( I+1 ) |
612 | 1 | pfleura2 | END IF |
613 | 1 | pfleura2 | WORK( I-LL+1 ) = COSR |
614 | 1 | pfleura2 | WORK( I-LL+1+NM1 ) = SINR |
615 | 1 | pfleura2 | WORK( I-LL+1+NM12 ) = COSL |
616 | 1 | pfleura2 | WORK( I-LL+1+NM13 ) = SINL |
617 | 1 | pfleura2 | 140 CONTINUE |
618 | 1 | pfleura2 | E( M-1 ) = F |
619 | 1 | pfleura2 | * |
620 | 1 | pfleura2 | * Update singular vectors |
621 | 1 | pfleura2 | * |
622 | 1 | pfleura2 | IF( NCVT.GT.0 ) |
623 | 1 | pfleura2 | $ CALL DLASR( 'L', 'V', 'F', M-LL+1, NCVT, WORK( 1 ), |
624 | 1 | pfleura2 | $ WORK( N ), VT( LL, 1 ), LDVT ) |
625 | 1 | pfleura2 | IF( NRU.GT.0 ) |
626 | 1 | pfleura2 | $ CALL DLASR( 'R', 'V', 'F', NRU, M-LL+1, WORK( NM12+1 ), |
627 | 1 | pfleura2 | $ WORK( NM13+1 ), U( 1, LL ), LDU ) |
628 | 1 | pfleura2 | IF( NCC.GT.0 ) |
629 | 1 | pfleura2 | $ CALL DLASR( 'L', 'V', 'F', M-LL+1, NCC, WORK( NM12+1 ), |
630 | 1 | pfleura2 | $ WORK( NM13+1 ), C( LL, 1 ), LDC ) |
631 | 1 | pfleura2 | * |
632 | 1 | pfleura2 | * Test convergence |
633 | 1 | pfleura2 | * |
634 | 1 | pfleura2 | IF( ABS( E( M-1 ) ).LE.THRESH ) |
635 | 1 | pfleura2 | $ E( M-1 ) = ZERO |
636 | 1 | pfleura2 | * |
637 | 1 | pfleura2 | ELSE |
638 | 1 | pfleura2 | * |
639 | 1 | pfleura2 | * Chase bulge from bottom to top |
640 | 1 | pfleura2 | * Save cosines and sines for later singular vector updates |
641 | 1 | pfleura2 | * |
642 | 1 | pfleura2 | F = ( ABS( D( M ) )-SHIFT )*( SIGN( ONE, D( M ) )+SHIFT / |
643 | 1 | pfleura2 | $ D( M ) ) |
644 | 1 | pfleura2 | G = E( M-1 ) |
645 | 1 | pfleura2 | DO 150 I = M, LL + 1, -1 |
646 | 1 | pfleura2 | CALL DLARTG( F, G, COSR, SINR, R ) |
647 | 1 | pfleura2 | IF( I.LT.M ) |
648 | 1 | pfleura2 | $ E( I ) = R |
649 | 1 | pfleura2 | F = COSR*D( I ) + SINR*E( I-1 ) |
650 | 1 | pfleura2 | E( I-1 ) = COSR*E( I-1 ) - SINR*D( I ) |
651 | 1 | pfleura2 | G = SINR*D( I-1 ) |
652 | 1 | pfleura2 | D( I-1 ) = COSR*D( I-1 ) |
653 | 1 | pfleura2 | CALL DLARTG( F, G, COSL, SINL, R ) |
654 | 1 | pfleura2 | D( I ) = R |
655 | 1 | pfleura2 | F = COSL*E( I-1 ) + SINL*D( I-1 ) |
656 | 1 | pfleura2 | D( I-1 ) = COSL*D( I-1 ) - SINL*E( I-1 ) |
657 | 1 | pfleura2 | IF( I.GT.LL+1 ) THEN |
658 | 1 | pfleura2 | G = SINL*E( I-2 ) |
659 | 1 | pfleura2 | E( I-2 ) = COSL*E( I-2 ) |
660 | 1 | pfleura2 | END IF |
661 | 1 | pfleura2 | WORK( I-LL ) = COSR |
662 | 1 | pfleura2 | WORK( I-LL+NM1 ) = -SINR |
663 | 1 | pfleura2 | WORK( I-LL+NM12 ) = COSL |
664 | 1 | pfleura2 | WORK( I-LL+NM13 ) = -SINL |
665 | 1 | pfleura2 | 150 CONTINUE |
666 | 1 | pfleura2 | E( LL ) = F |
667 | 1 | pfleura2 | * |
668 | 1 | pfleura2 | * Test convergence |
669 | 1 | pfleura2 | * |
670 | 1 | pfleura2 | IF( ABS( E( LL ) ).LE.THRESH ) |
671 | 1 | pfleura2 | $ E( LL ) = ZERO |
672 | 1 | pfleura2 | * |
673 | 1 | pfleura2 | * Update singular vectors if desired |
674 | 1 | pfleura2 | * |
675 | 1 | pfleura2 | IF( NCVT.GT.0 ) |
676 | 1 | pfleura2 | $ CALL DLASR( 'L', 'V', 'B', M-LL+1, NCVT, WORK( NM12+1 ), |
677 | 1 | pfleura2 | $ WORK( NM13+1 ), VT( LL, 1 ), LDVT ) |
678 | 1 | pfleura2 | IF( NRU.GT.0 ) |
679 | 1 | pfleura2 | $ CALL DLASR( 'R', 'V', 'B', NRU, M-LL+1, WORK( 1 ), |
680 | 1 | pfleura2 | $ WORK( N ), U( 1, LL ), LDU ) |
681 | 1 | pfleura2 | IF( NCC.GT.0 ) |
682 | 1 | pfleura2 | $ CALL DLASR( 'L', 'V', 'B', M-LL+1, NCC, WORK( 1 ), |
683 | 1 | pfleura2 | $ WORK( N ), C( LL, 1 ), LDC ) |
684 | 1 | pfleura2 | END IF |
685 | 1 | pfleura2 | END IF |
686 | 1 | pfleura2 | * |
687 | 1 | pfleura2 | * QR iteration finished, go back and check convergence |
688 | 1 | pfleura2 | * |
689 | 1 | pfleura2 | GO TO 60 |
690 | 1 | pfleura2 | * |
691 | 1 | pfleura2 | * All singular values converged, so make them positive |
692 | 1 | pfleura2 | * |
693 | 1 | pfleura2 | 160 CONTINUE |
694 | 1 | pfleura2 | DO 170 I = 1, N |
695 | 1 | pfleura2 | IF( D( I ).LT.ZERO ) THEN |
696 | 1 | pfleura2 | D( I ) = -D( I ) |
697 | 1 | pfleura2 | * |
698 | 1 | pfleura2 | * Change sign of singular vectors, if desired |
699 | 1 | pfleura2 | * |
700 | 1 | pfleura2 | IF( NCVT.GT.0 ) |
701 | 1 | pfleura2 | $ CALL DSCAL( NCVT, NEGONE, VT( I, 1 ), LDVT ) |
702 | 1 | pfleura2 | END IF |
703 | 1 | pfleura2 | 170 CONTINUE |
704 | 1 | pfleura2 | * |
705 | 1 | pfleura2 | * Sort the singular values into decreasing order (insertion sort on |
706 | 1 | pfleura2 | * singular values, but only one transposition per singular vector) |
707 | 1 | pfleura2 | * |
708 | 1 | pfleura2 | DO 190 I = 1, N - 1 |
709 | 1 | pfleura2 | * |
710 | 1 | pfleura2 | * Scan for smallest D(I) |
711 | 1 | pfleura2 | * |
712 | 1 | pfleura2 | ISUB = 1 |
713 | 1 | pfleura2 | SMIN = D( 1 ) |
714 | 1 | pfleura2 | DO 180 J = 2, N + 1 - I |
715 | 1 | pfleura2 | IF( D( J ).LE.SMIN ) THEN |
716 | 1 | pfleura2 | ISUB = J |
717 | 1 | pfleura2 | SMIN = D( J ) |
718 | 1 | pfleura2 | END IF |
719 | 1 | pfleura2 | 180 CONTINUE |
720 | 1 | pfleura2 | IF( ISUB.NE.N+1-I ) THEN |
721 | 1 | pfleura2 | * |
722 | 1 | pfleura2 | * Swap singular values and vectors |
723 | 1 | pfleura2 | * |
724 | 1 | pfleura2 | D( ISUB ) = D( N+1-I ) |
725 | 1 | pfleura2 | D( N+1-I ) = SMIN |
726 | 1 | pfleura2 | IF( NCVT.GT.0 ) |
727 | 1 | pfleura2 | $ CALL DSWAP( NCVT, VT( ISUB, 1 ), LDVT, VT( N+1-I, 1 ), |
728 | 1 | pfleura2 | $ LDVT ) |
729 | 1 | pfleura2 | IF( NRU.GT.0 ) |
730 | 1 | pfleura2 | $ CALL DSWAP( NRU, U( 1, ISUB ), 1, U( 1, N+1-I ), 1 ) |
731 | 1 | pfleura2 | IF( NCC.GT.0 ) |
732 | 1 | pfleura2 | $ CALL DSWAP( NCC, C( ISUB, 1 ), LDC, C( N+1-I, 1 ), LDC ) |
733 | 1 | pfleura2 | END IF |
734 | 1 | pfleura2 | 190 CONTINUE |
735 | 1 | pfleura2 | GO TO 220 |
736 | 1 | pfleura2 | * |
737 | 1 | pfleura2 | * Maximum number of iterations exceeded, failure to converge |
738 | 1 | pfleura2 | * |
739 | 1 | pfleura2 | 200 CONTINUE |
740 | 1 | pfleura2 | INFO = 0 |
741 | 1 | pfleura2 | DO 210 I = 1, N - 1 |
742 | 1 | pfleura2 | IF( E( I ).NE.ZERO ) |
743 | 1 | pfleura2 | $ INFO = INFO + 1 |
744 | 1 | pfleura2 | 210 CONTINUE |
745 | 1 | pfleura2 | 220 CONTINUE |
746 | 1 | pfleura2 | RETURN |
747 | 1 | pfleura2 | * |
748 | 1 | pfleura2 | * End of DBDSQR |
749 | 1 | pfleura2 | * |
750 | 1 | pfleura2 | END |