LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
slasd5.f
Go to the documentation of this file.
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.
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download SLASD5 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slasd5.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slasd5.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slasd5.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE SLASD5( I, D, Z, DELTA, RHO, DSIGMA, WORK )
22 *
23 * .. Scalar Arguments ..
24 * INTEGER I
25 * REAL DSIGMA, RHO
26 * ..
27 * .. Array Arguments ..
28 * REAL D( 2 ), DELTA( 2 ), WORK( 2 ), Z( 2 )
29 * ..
30 *
31 *
32 *> \par Purpose:
33 * =============
34 *>
35 *> \verbatim
36 *>
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
39 *> matrix
40 *>
41 *> diag( D ) * diag( D ) + RHO * Z * transpose(Z) .
42 *>
43 *> The diagonal entries in the array D are assumed to satisfy
44 *>
45 *> 0 <= D(i) < D(j) for i < j .
46 *>
47 *> We also assume RHO > 0 and that the Euclidean norm of the vector
48 *> Z is one.
49 *> \endverbatim
50 *
51 * Arguments:
52 * ==========
53 *
54 *> \param[in] I
55 *> \verbatim
56 *> I is INTEGER
57 *> The index of the eigenvalue to be computed. I = 1 or I = 2.
58 *> \endverbatim
59 *>
60 *> \param[in] D
61 *> \verbatim
62 *> D is REAL array, dimension (2)
63 *> The original eigenvalues. We assume 0 <= D(1) < D(2).
64 *> \endverbatim
65 *>
66 *> \param[in] Z
67 *> \verbatim
68 *> Z is REAL array, dimension (2)
69 *> The components of the updating vector.
70 *> \endverbatim
71 *>
72 *> \param[out] DELTA
73 *> \verbatim
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.
78 *> \endverbatim
79 *>
80 *> \param[in] RHO
81 *> \verbatim
82 *> RHO is REAL
83 *> The scalar in the symmetric updating formula.
84 *> \endverbatim
85 *>
86 *> \param[out] DSIGMA
87 *> \verbatim
88 *> DSIGMA is REAL
89 *> The computed sigma_I, the I-th updated eigenvalue.
90 *> \endverbatim
91 *>
92 *> \param[out] WORK
93 *> \verbatim
94 *> WORK is REAL array, dimension (2)
95 *> WORK contains (D(j) + sigma_I) in its j-th component.
96 *> \endverbatim
97 *
98 * Authors:
99 * ========
100 *
101 *> \author Univ. of Tennessee
102 *> \author Univ. of California Berkeley
103 *> \author Univ. of Colorado Denver
104 *> \author NAG Ltd.
105 *
106 *> \date September 2012
107 *
108 *> \ingroup auxOTHERauxiliary
109 *
110 *> \par Contributors:
111 * ==================
112 *>
113 *> Ren-Cang Li, Computer Science Division, University of California
114 *> at Berkeley, USA
115 *>
116 * =====================================================================
117  SUBROUTINE slasd5( I, D, Z, DELTA, RHO, DSIGMA, WORK )
118 *
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..--
122 * September 2012
123 *
124 * .. Scalar Arguments ..
125  INTEGER i
126  REAL dsigma, rho
127 * ..
128 * .. Array Arguments ..
129  REAL d( 2 ), delta( 2 ), work( 2 ), z( 2 )
130 * ..
131 *
132 * =====================================================================
133 *
134 * .. Parameters ..
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 )
138 * ..
139 * .. Local Scalars ..
140  REAL b, c, del, delsq, tau, w
141 * ..
142 * .. Intrinsic Functions ..
143  INTRINSIC abs, sqrt
144 * ..
145 * .. Executable Statements ..
146 *
147  del = d( 2 ) - d( 1 )
148  delsq = del*( d( 2 )+d( 1 ) )
149  IF( i.EQ.1 ) THEN
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
152  IF( w.GT.zero ) THEN
153  b = delsq + rho*( z( 1 )*z( 1 )+z( 2 )*z( 2 ) )
154  c = rho*z( 1 )*z( 1 )*delsq
155 *
156 * B > ZERO, always
157 *
158 * The following TAU is DSIGMA * DSIGMA - D( 1 ) * D( 1 )
159 *
160  tau = two*c / ( b+sqrt( abs( b*b-four*c ) ) )
161 *
162 * The following TAU is DSIGMA - D( 1 )
163 *
164  tau = tau / ( d( 1 )+sqrt( d( 1 )*d( 1 )+tau ) )
165  dsigma = d( 1 ) + tau
166  delta( 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 )
172  ELSE
173  b = -delsq + rho*( z( 1 )*z( 1 )+z( 2 )*z( 2 ) )
174  c = rho*z( 2 )*z( 2 )*delsq
175 *
176 * The following TAU is DSIGMA * DSIGMA - D( 2 ) * D( 2 )
177 *
178  IF( b.GT.zero ) THEN
179  tau = -two*c / ( b+sqrt( b*b+four*c ) )
180  ELSE
181  tau = ( b-sqrt( b*b+four*c ) ) / two
182  END IF
183 *
184 * The following TAU is DSIGMA - D( 2 )
185 *
186  tau = tau / ( d( 2 )+sqrt( abs( d( 2 )*d( 2 )+tau ) ) )
187  dsigma = d( 2 ) + tau
188  delta( 1 ) = -( del+tau )
189  delta( 2 ) = -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
194  END IF
195 * TEMP = SQRT( DELTA( 1 )*DELTA( 1 )+DELTA( 2 )*DELTA( 2 ) )
196 * DELTA( 1 ) = DELTA( 1 ) / TEMP
197 * DELTA( 2 ) = DELTA( 2 ) / TEMP
198  ELSE
199 *
200 * Now I=2
201 *
202  b = -delsq + rho*( z( 1 )*z( 1 )+z( 2 )*z( 2 ) )
203  c = rho*z( 2 )*z( 2 )*delsq
204 *
205 * The following TAU is DSIGMA * DSIGMA - D( 2 ) * D( 2 )
206 *
207  IF( b.GT.zero ) THEN
208  tau = ( b+sqrt( b*b+four*c ) ) / two
209  ELSE
210  tau = two*c / ( -b+sqrt( b*b+four*c ) )
211  END IF
212 *
213 * The following TAU is DSIGMA - D( 2 )
214 *
215  tau = tau / ( d( 2 )+sqrt( d( 2 )*d( 2 )+tau ) )
216  dsigma = d( 2 ) + tau
217  delta( 1 ) = -( del+tau )
218  delta( 2 ) = -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
226  END IF
227  return
228 *
229 * End of SLASD5
230 *
231  END