LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
slasd8.f
Go to the documentation of this file.
1 *> \brief \b SLASD8 finds the square roots of the roots of the secular equation, and stores, for each element in D, the distance to its two nearest poles. Used by sbdsdc.
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download SLASD8 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slasd8.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slasd8.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slasd8.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE SLASD8( ICOMPQ, K, D, Z, VF, VL, DIFL, DIFR, LDDIFR,
22 * DSIGMA, WORK, INFO )
23 *
24 * .. Scalar Arguments ..
25 * INTEGER ICOMPQ, INFO, K, LDDIFR
26 * ..
27 * .. Array Arguments ..
28 * REAL D( * ), DIFL( * ), DIFR( LDDIFR, * ),
29 * $ DSIGMA( * ), VF( * ), VL( * ), WORK( * ),
30 * $ Z( * )
31 * ..
32 *
33 *
34 *> \par Purpose:
35 * =============
36 *>
37 *> \verbatim
38 *>
39 *> SLASD8 finds the square roots of the roots of the secular equation,
40 *> as defined by the values in DSIGMA and Z. It makes the appropriate
41 *> calls to SLASD4, and stores, for each element in D, the distance
42 *> to its two nearest poles (elements in DSIGMA). It also updates
43 *> the arrays VF and VL, the first and last components of all the
44 *> right singular vectors of the original bidiagonal matrix.
45 *>
46 *> SLASD8 is called from SLASD6.
47 *> \endverbatim
48 *
49 * Arguments:
50 * ==========
51 *
52 *> \param[in] ICOMPQ
53 *> \verbatim
54 *> ICOMPQ is INTEGER
55 *> Specifies whether singular vectors are to be computed in
56 *> factored form in the calling routine:
57 *> = 0: Compute singular values only.
58 *> = 1: Compute singular vectors in factored form as well.
59 *> \endverbatim
60 *>
61 *> \param[in] K
62 *> \verbatim
63 *> K is INTEGER
64 *> The number of terms in the rational function to be solved
65 *> by SLASD4. K >= 1.
66 *> \endverbatim
67 *>
68 *> \param[out] D
69 *> \verbatim
70 *> D is REAL array, dimension ( K )
71 *> On output, D contains the updated singular values.
72 *> \endverbatim
73 *>
74 *> \param[in,out] Z
75 *> \verbatim
76 *> Z is REAL array, dimension ( K )
77 *> On entry, the first K elements of this array contain the
78 *> components of the deflation-adjusted updating row vector.
79 *> On exit, Z is updated.
80 *> \endverbatim
81 *>
82 *> \param[in,out] VF
83 *> \verbatim
84 *> VF is REAL array, dimension ( K )
85 *> On entry, VF contains information passed through DBEDE8.
86 *> On exit, VF contains the first K components of the first
87 *> components of all right singular vectors of the bidiagonal
88 *> matrix.
89 *> \endverbatim
90 *>
91 *> \param[in,out] VL
92 *> \verbatim
93 *> VL is REAL array, dimension ( K )
94 *> On entry, VL contains information passed through DBEDE8.
95 *> On exit, VL contains the first K components of the last
96 *> components of all right singular vectors of the bidiagonal
97 *> matrix.
98 *> \endverbatim
99 *>
100 *> \param[out] DIFL
101 *> \verbatim
102 *> DIFL is REAL array, dimension ( K )
103 *> On exit, DIFL(I) = D(I) - DSIGMA(I).
104 *> \endverbatim
105 *>
106 *> \param[out] DIFR
107 *> \verbatim
108 *> DIFR is REAL array,
109 *> dimension ( LDDIFR, 2 ) if ICOMPQ = 1 and
110 *> dimension ( K ) if ICOMPQ = 0.
111 *> On exit, DIFR(I,1) = D(I) - DSIGMA(I+1), DIFR(K,1) is not
112 *> defined and will not be referenced.
113 *>
114 *> If ICOMPQ = 1, DIFR(1:K,2) is an array containing the
115 *> normalizing factors for the right singular vector matrix.
116 *> \endverbatim
117 *>
118 *> \param[in] LDDIFR
119 *> \verbatim
120 *> LDDIFR is INTEGER
121 *> The leading dimension of DIFR, must be at least K.
122 *> \endverbatim
123 *>
124 *> \param[in,out] DSIGMA
125 *> \verbatim
126 *> DSIGMA is REAL array, dimension ( K )
127 *> On entry, the first K elements of this array contain the old
128 *> roots of the deflated updating problem. These are the poles
129 *> of the secular equation.
130 *> On exit, the elements of DSIGMA may be very slightly altered
131 *> in value.
132 *> \endverbatim
133 *>
134 *> \param[out] WORK
135 *> \verbatim
136 *> WORK is REAL array, dimension at least 3 * K
137 *> \endverbatim
138 *>
139 *> \param[out] INFO
140 *> \verbatim
141 *> INFO is INTEGER
142 *> = 0: successful exit.
143 *> < 0: if INFO = -i, the i-th argument had an illegal value.
144 *> > 0: if INFO = 1, a singular value did not converge
145 *> \endverbatim
146 *
147 * Authors:
148 * ========
149 *
150 *> \author Univ. of Tennessee
151 *> \author Univ. of California Berkeley
152 *> \author Univ. of Colorado Denver
153 *> \author NAG Ltd.
154 *
155 *> \date November 2015
156 *
157 *> \ingroup auxOTHERauxiliary
158 *
159 *> \par Contributors:
160 * ==================
161 *>
162 *> Ming Gu and Huan Ren, Computer Science Division, University of
163 *> California at Berkeley, USA
164 *>
165 * =====================================================================
166  SUBROUTINE slasd8( ICOMPQ, K, D, Z, VF, VL, DIFL, DIFR, LDDIFR,
167  $ dsigma, work, info )
168 *
169 * -- LAPACK auxiliary routine (version 3.6.0) --
170 * -- LAPACK is a software package provided by Univ. of Tennessee, --
171 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
172 * November 2015
173 *
174 * .. Scalar Arguments ..
175  INTEGER ICOMPQ, INFO, K, LDDIFR
176 * ..
177 * .. Array Arguments ..
178  REAL D( * ), DIFL( * ), DIFR( lddifr, * ),
179  $ dsigma( * ), vf( * ), vl( * ), work( * ),
180  $ z( * )
181 * ..
182 *
183 * =====================================================================
184 *
185 * .. Parameters ..
186  REAL ONE
187  parameter ( one = 1.0e+0 )
188 * ..
189 * .. Local Scalars ..
190  INTEGER I, IWK1, IWK2, IWK2I, IWK3, IWK3I, J
191  REAL DIFLJ, DIFRJ, DJ, DSIGJ, DSIGJP, RHO, TEMP
192 * ..
193 * .. External Subroutines ..
194  EXTERNAL scopy, slascl, slasd4, slaset, xerbla
195 * ..
196 * .. External Functions ..
197  REAL SDOT, SLAMC3, SNRM2
198  EXTERNAL sdot, slamc3, snrm2
199 * ..
200 * .. Intrinsic Functions ..
201  INTRINSIC abs, sign, sqrt
202 * ..
203 * .. Executable Statements ..
204 *
205 * Test the input parameters.
206 *
207  info = 0
208 *
209  IF( ( icompq.LT.0 ) .OR. ( icompq.GT.1 ) ) THEN
210  info = -1
211  ELSE IF( k.LT.1 ) THEN
212  info = -2
213  ELSE IF( lddifr.LT.k ) THEN
214  info = -9
215  END IF
216  IF( info.NE.0 ) THEN
217  CALL xerbla( 'SLASD8', -info )
218  RETURN
219  END IF
220 *
221 * Quick return if possible
222 *
223  IF( k.EQ.1 ) THEN
224  d( 1 ) = abs( z( 1 ) )
225  difl( 1 ) = d( 1 )
226  IF( icompq.EQ.1 ) THEN
227  difl( 2 ) = one
228  difr( 1, 2 ) = one
229  END IF
230  RETURN
231  END IF
232 *
233 * Modify values DSIGMA(i) to make sure all DSIGMA(i)-DSIGMA(j) can
234 * be computed with high relative accuracy (barring over/underflow).
235 * This is a problem on machines without a guard digit in
236 * add/subtract (Cray XMP, Cray YMP, Cray C 90 and Cray 2).
237 * The following code replaces DSIGMA(I) by 2*DSIGMA(I)-DSIGMA(I),
238 * which on any of these machines zeros out the bottommost
239 * bit of DSIGMA(I) if it is 1; this makes the subsequent
240 * subtractions DSIGMA(I)-DSIGMA(J) unproblematic when cancellation
241 * occurs. On binary machines with a guard digit (almost all
242 * machines) it does not change DSIGMA(I) at all. On hexadecimal
243 * and decimal machines with a guard digit, it slightly
244 * changes the bottommost bits of DSIGMA(I). It does not account
245 * for hexadecimal or decimal machines without guard digits
246 * (we know of none). We use a subroutine call to compute
247 * 2*DLAMBDA(I) to prevent optimizing compilers from eliminating
248 * this code.
249 *
250  DO 10 i = 1, k
251  dsigma( i ) = slamc3( dsigma( i ), dsigma( i ) ) - dsigma( i )
252  10 CONTINUE
253 *
254 * Book keeping.
255 *
256  iwk1 = 1
257  iwk2 = iwk1 + k
258  iwk3 = iwk2 + k
259  iwk2i = iwk2 - 1
260  iwk3i = iwk3 - 1
261 *
262 * Normalize Z.
263 *
264  rho = snrm2( k, z, 1 )
265  CALL slascl( 'G', 0, 0, rho, one, k, 1, z, k, info )
266  rho = rho*rho
267 *
268 * Initialize WORK(IWK3).
269 *
270  CALL slaset( 'A', k, 1, one, one, work( iwk3 ), k )
271 *
272 * Compute the updated singular values, the arrays DIFL, DIFR,
273 * and the updated Z.
274 *
275  DO 40 j = 1, k
276  CALL slasd4( k, j, dsigma, z, work( iwk1 ), rho, d( j ),
277  $ work( iwk2 ), info )
278 *
279 * If the root finder fails, report the convergence failure.
280 *
281  IF( info.NE.0 ) THEN
282  RETURN
283  END IF
284  work( iwk3i+j ) = work( iwk3i+j )*work( j )*work( iwk2i+j )
285  difl( j ) = -work( j )
286  difr( j, 1 ) = -work( j+1 )
287  DO 20 i = 1, j - 1
288  work( iwk3i+i ) = work( iwk3i+i )*work( i )*
289  $ work( iwk2i+i ) / ( dsigma( i )-
290  $ dsigma( j ) ) / ( dsigma( i )+
291  $ dsigma( j ) )
292  20 CONTINUE
293  DO 30 i = j + 1, k
294  work( iwk3i+i ) = work( iwk3i+i )*work( i )*
295  $ work( iwk2i+i ) / ( dsigma( i )-
296  $ dsigma( j ) ) / ( dsigma( i )+
297  $ dsigma( j ) )
298  30 CONTINUE
299  40 CONTINUE
300 *
301 * Compute updated Z.
302 *
303  DO 50 i = 1, k
304  z( i ) = sign( sqrt( abs( work( iwk3i+i ) ) ), z( i ) )
305  50 CONTINUE
306 *
307 * Update VF and VL.
308 *
309  DO 80 j = 1, k
310  diflj = difl( j )
311  dj = d( j )
312  dsigj = -dsigma( j )
313  IF( j.LT.k ) THEN
314  difrj = -difr( j, 1 )
315  dsigjp = -dsigma( j+1 )
316  END IF
317  work( j ) = -z( j ) / diflj / ( dsigma( j )+dj )
318  DO 60 i = 1, j - 1
319  work( i ) = z( i ) / ( slamc3( dsigma( i ), dsigj )-diflj )
320  $ / ( dsigma( i )+dj )
321  60 CONTINUE
322  DO 70 i = j + 1, k
323  work( i ) = z( i ) / ( slamc3( dsigma( i ), dsigjp )+difrj )
324  $ / ( dsigma( i )+dj )
325  70 CONTINUE
326  temp = snrm2( k, work, 1 )
327  work( iwk2i+j ) = sdot( k, work, 1, vf, 1 ) / temp
328  work( iwk3i+j ) = sdot( k, work, 1, vl, 1 ) / temp
329  IF( icompq.EQ.1 ) THEN
330  difr( j, 2 ) = temp
331  END IF
332  80 CONTINUE
333 *
334  CALL scopy( k, work( iwk2 ), 1, vf, 1 )
335  CALL scopy( k, work( iwk3 ), 1, vl, 1 )
336 *
337  RETURN
338 *
339 * End of SLASD8
340 *
341  END
342 
subroutine slasd8(ICOMPQ, K, D, Z, VF, VL, DIFL, DIFR, LDDIFR, DSIGMA, WORK, INFO)
SLASD8 finds the square roots of the roots of the secular equation, and stores, for each element in D...
Definition: slasd8.f:168
subroutine slascl(TYPE, KL, KU, CFROM, CTO, M, N, A, LDA, INFO)
SLASCL multiplies a general rectangular matrix by a real scalar defined as cto/cfrom.
Definition: slascl.f:145
subroutine slasd4(N, I, D, Z, DELTA, RHO, SIGMA, WORK, INFO)
SLASD4 computes the square root of the i-th updated eigenvalue of a positive symmetric rank-one modif...
Definition: slasd4.f:155
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine slaset(UPLO, M, N, ALPHA, BETA, A, LDA)
SLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values...
Definition: slaset.f:112
subroutine scopy(N, SX, INCX, SY, INCY)
SCOPY
Definition: scopy.f:53