1 *> \brief \b SLASD5 computes the square root of the i-th eigenvalue of a positive symmetric rank-one modification of a 2-by-2 diagonal matrix. Used by sbdsdc.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download SLASD5 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slasd5.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slasd5.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slasd5.f">
21 * SUBROUTINE SLASD5( I, D, Z, DELTA, RHO, DSIGMA, WORK )
23 * .. Scalar Arguments ..
27 * .. Array Arguments ..
28 * REAL D( 2 ), DELTA( 2 ), WORK( 2 ), Z( 2 )
37 *> This subroutine computes the square root of the I-th eigenvalue
38 *> of a positive symmetric rank-one modification of a 2-by-2 diagonal
41 *> diag( D ) * diag( D ) + RHO * Z * transpose(Z) .
43 *> The diagonal entries in the array D are assumed to satisfy
45 *> 0 <= D(i) < D(j) for i < j .
47 *> We also assume RHO > 0 and that the Euclidean norm of the vector
57 *> The index of the eigenvalue to be computed. I = 1 or I = 2.
62 *> D is REAL array, dimension (2)
63 *> The original eigenvalues. We assume 0 <= D(1) < D(2).
68 *> Z is REAL array, dimension (2)
69 *> The components of the updating vector.
74 *> DELTA is REAL array, dimension (2)
75 *> Contains (D(j) - sigma_I) in its j-th component.
76 *> The vector DELTA contains the information necessary
77 *> to construct the eigenvectors.
83 *> The scalar in the symmetric updating formula.
89 *> The computed sigma_I, the I-th updated eigenvalue.
94 *> WORK is REAL array, dimension (2)
95 *> WORK contains (D(j) + sigma_I) in its j-th component.
101 *> \author Univ. of Tennessee
102 *> \author Univ. of California Berkeley
103 *> \author Univ. of Colorado Denver
106 *> \date September 2012
108 *> \ingroup OTHERauxiliary
110 *> \par Contributors:
113 *> Ren-Cang Li, Computer Science Division, University of California
116 * =====================================================================
117 SUBROUTINE SLASD5( I, D, Z, DELTA, RHO, DSIGMA, WORK )
119 * -- LAPACK auxiliary routine (version 3.4.2) --
120 * -- LAPACK is a software package provided by Univ. of Tennessee, --
121 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
124 * .. Scalar Arguments ..
128 * .. Array Arguments ..
129 REAL D( 2 ), DELTA( 2 ), WORK( 2 ), Z( 2 )
132 * =====================================================================
135 REAL ZERO, ONE, TWO, THREE, FOUR
136 PARAMETER ( ZERO = 0.0E+0, ONE = 1.0E+0, TWO = 2.0E+0,
137 $ THREE = 3.0E+0, FOUR = 4.0E+0 )
139 * .. Local Scalars ..
140 REAL B, C, DEL, DELSQ, TAU, W
142 * .. Intrinsic Functions ..
145 * .. Executable Statements ..
147 DEL = D( 2 ) - D( 1 )
148 DELSQ = DEL*( D( 2 )+D( 1 ) )
150 W = ONE + FOUR*RHO*( Z( 2 )*Z( 2 ) / ( D( 1 )+THREE*D( 2 ) )-
151 $ Z( 1 )*Z( 1 ) / ( THREE*D( 1 )+D( 2 ) ) ) / DEL
153 B = DELSQ + RHO*( Z( 1 )*Z( 1 )+Z( 2 )*Z( 2 ) )
154 C = RHO*Z( 1 )*Z( 1 )*DELSQ
158 * The following TAU is DSIGMA * DSIGMA - D( 1 ) * D( 1 )
160 TAU = TWO*C / ( B+SQRT( ABS( B*B-FOUR*C ) ) )
162 * The following TAU is DSIGMA - D( 1 )
164 TAU = TAU / ( D( 1 )+SQRT( D( 1 )*D( 1 )+TAU ) )
165 DSIGMA = D( 1 ) + TAU
167 DELTA( 2 ) = DEL - TAU
168 WORK( 1 ) = TWO*D( 1 ) + TAU
169 WORK( 2 ) = ( D( 1 )+TAU ) + D( 2 )
170 * DELTA( 1 ) = -Z( 1 ) / TAU
171 * DELTA( 2 ) = Z( 2 ) / ( DEL-TAU )
173 B = -DELSQ + RHO*( Z( 1 )*Z( 1 )+Z( 2 )*Z( 2 ) )
174 C = RHO*Z( 2 )*Z( 2 )*DELSQ
176 * The following TAU is DSIGMA * DSIGMA - D( 2 ) * D( 2 )
179 TAU = -TWO*C / ( B+SQRT( B*B+FOUR*C ) )
181 TAU = ( B-SQRT( B*B+FOUR*C ) ) / TWO
184 * The following TAU is DSIGMA - D( 2 )
186 TAU = TAU / ( D( 2 )+SQRT( ABS( D( 2 )*D( 2 )+TAU ) ) )
187 DSIGMA = D( 2 ) + TAU
188 DELTA( 1 ) = -( DEL+TAU )
190 WORK( 1 ) = D( 1 ) + TAU + D( 2 )
191 WORK( 2 ) = TWO*D( 2 ) + TAU
192 * DELTA( 1 ) = -Z( 1 ) / ( DEL+TAU )
193 * DELTA( 2 ) = -Z( 2 ) / TAU
195 * TEMP = SQRT( DELTA( 1 )*DELTA( 1 )+DELTA( 2 )*DELTA( 2 ) )
196 * DELTA( 1 ) = DELTA( 1 ) / TEMP
197 * DELTA( 2 ) = DELTA( 2 ) / TEMP
202 B = -DELSQ + RHO*( Z( 1 )*Z( 1 )+Z( 2 )*Z( 2 ) )
203 C = RHO*Z( 2 )*Z( 2 )*DELSQ
205 * The following TAU is DSIGMA * DSIGMA - D( 2 ) * D( 2 )
208 TAU = ( B+SQRT( B*B+FOUR*C ) ) / TWO
210 TAU = TWO*C / ( -B+SQRT( B*B+FOUR*C ) )
213 * The following TAU is DSIGMA - D( 2 )
215 TAU = TAU / ( D( 2 )+SQRT( D( 2 )*D( 2 )+TAU ) )
216 DSIGMA = D( 2 ) + TAU
217 DELTA( 1 ) = -( DEL+TAU )
219 WORK( 1 ) = D( 1 ) + TAU + D( 2 )
220 WORK( 2 ) = TWO*D( 2 ) + TAU
221 * DELTA( 1 ) = -Z( 1 ) / ( DEL+TAU )
222 * DELTA( 2 ) = -Z( 2 ) / TAU
223 * TEMP = SQRT( DELTA( 1 )*DELTA( 1 )+DELTA( 2 )*DELTA( 2 ) )
224 * DELTA( 1 ) = DELTA( 1 ) / TEMP
225 * DELTA( 2 ) = DELTA( 2 ) / TEMP