LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
slaed5.f
Go to the documentation of this file.
1 *> \brief \b SLAED5 used by sstedc. Solves the 2-by-2 secular equation.
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download SLAED5 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slaed5.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slaed5.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slaed5.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE SLAED5( I, D, Z, DELTA, RHO, DLAM )
22 *
23 * .. Scalar Arguments ..
24 * INTEGER I
25 * REAL DLAM, RHO
26 * ..
27 * .. Array Arguments ..
28 * REAL D( 2 ), DELTA( 2 ), Z( 2 )
29 * ..
30 *
31 *
32 *> \par Purpose:
33 * =============
34 *>
35 *> \verbatim
36 *>
37 *> This subroutine computes the I-th eigenvalue of a symmetric rank-one
38 *> modification of a 2-by-2 diagonal matrix
39 *>
40 *> diag( D ) + RHO * Z * transpose(Z) .
41 *>
42 *> The diagonal elements in the array D are assumed to satisfy
43 *>
44 *> D(i) < D(j) for i < j .
45 *>
46 *> We also assume RHO > 0 and that the Euclidean norm of the vector
47 *> Z is one.
48 *> \endverbatim
49 *
50 * Arguments:
51 * ==========
52 *
53 *> \param[in] I
54 *> \verbatim
55 *> I is INTEGER
56 *> The index of the eigenvalue to be computed. I = 1 or I = 2.
57 *> \endverbatim
58 *>
59 *> \param[in] D
60 *> \verbatim
61 *> D is REAL array, dimension (2)
62 *> The original eigenvalues. We assume D(1) < D(2).
63 *> \endverbatim
64 *>
65 *> \param[in] Z
66 *> \verbatim
67 *> Z is REAL array, dimension (2)
68 *> The components of the updating vector.
69 *> \endverbatim
70 *>
71 *> \param[out] DELTA
72 *> \verbatim
73 *> DELTA is REAL array, dimension (2)
74 *> The vector DELTA contains the information necessary
75 *> to construct the eigenvectors.
76 *> \endverbatim
77 *>
78 *> \param[in] RHO
79 *> \verbatim
80 *> RHO is REAL
81 *> The scalar in the symmetric updating formula.
82 *> \endverbatim
83 *>
84 *> \param[out] DLAM
85 *> \verbatim
86 *> DLAM is REAL
87 *> The computed lambda_I, the I-th updated eigenvalue.
88 *> \endverbatim
89 *
90 * Authors:
91 * ========
92 *
93 *> \author Univ. of Tennessee
94 *> \author Univ. of California Berkeley
95 *> \author Univ. of Colorado Denver
96 *> \author NAG Ltd.
97 *
98 *> \date September 2012
99 *
100 *> \ingroup auxOTHERcomputational
101 *
102 *> \par Contributors:
103 * ==================
104 *>
105 *> Ren-Cang Li, Computer Science Division, University of California
106 *> at Berkeley, USA
107 *>
108 * =====================================================================
109  SUBROUTINE slaed5( I, D, Z, DELTA, RHO, DLAM )
110 *
111 * -- LAPACK computational routine (version 3.4.2) --
112 * -- LAPACK is a software package provided by Univ. of Tennessee, --
113 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
114 * September 2012
115 *
116 * .. Scalar Arguments ..
117  INTEGER i
118  REAL dlam, rho
119 * ..
120 * .. Array Arguments ..
121  REAL d( 2 ), delta( 2 ), z( 2 )
122 * ..
123 *
124 * =====================================================================
125 *
126 * .. Parameters ..
127  REAL zero, one, two, four
128  parameter( zero = 0.0e0, one = 1.0e0, two = 2.0e0,
129  $ four = 4.0e0 )
130 * ..
131 * .. Local Scalars ..
132  REAL b, c, del, tau, temp, w
133 * ..
134 * .. Intrinsic Functions ..
135  INTRINSIC abs, sqrt
136 * ..
137 * .. Executable Statements ..
138 *
139  del = d( 2 ) - d( 1 )
140  IF( i.EQ.1 ) THEN
141  w = one + two*rho*( z( 2 )*z( 2 )-z( 1 )*z( 1 ) ) / del
142  IF( w.GT.zero ) THEN
143  b = del + rho*( z( 1 )*z( 1 )+z( 2 )*z( 2 ) )
144  c = rho*z( 1 )*z( 1 )*del
145 *
146 * B > ZERO, always
147 *
148  tau = two*c / ( b+sqrt( abs( b*b-four*c ) ) )
149  dlam = d( 1 ) + tau
150  delta( 1 ) = -z( 1 ) / tau
151  delta( 2 ) = z( 2 ) / ( del-tau )
152  ELSE
153  b = -del + rho*( z( 1 )*z( 1 )+z( 2 )*z( 2 ) )
154  c = rho*z( 2 )*z( 2 )*del
155  IF( b.GT.zero ) THEN
156  tau = -two*c / ( b+sqrt( b*b+four*c ) )
157  ELSE
158  tau = ( b-sqrt( b*b+four*c ) ) / two
159  END IF
160  dlam = d( 2 ) + tau
161  delta( 1 ) = -z( 1 ) / ( del+tau )
162  delta( 2 ) = -z( 2 ) / tau
163  END IF
164  temp = sqrt( delta( 1 )*delta( 1 )+delta( 2 )*delta( 2 ) )
165  delta( 1 ) = delta( 1 ) / temp
166  delta( 2 ) = delta( 2 ) / temp
167  ELSE
168 *
169 * Now I=2
170 *
171  b = -del + rho*( z( 1 )*z( 1 )+z( 2 )*z( 2 ) )
172  c = rho*z( 2 )*z( 2 )*del
173  IF( b.GT.zero ) THEN
174  tau = ( b+sqrt( b*b+four*c ) ) / two
175  ELSE
176  tau = two*c / ( -b+sqrt( b*b+four*c ) )
177  END IF
178  dlam = d( 2 ) + tau
179  delta( 1 ) = -z( 1 ) / ( del+tau )
180  delta( 2 ) = -z( 2 ) / tau
181  temp = sqrt( delta( 1 )*delta( 1 )+delta( 2 )*delta( 2 ) )
182  delta( 1 ) = delta( 1 ) / temp
183  delta( 2 ) = delta( 2 ) / temp
184  END IF
185  return
186 *
187 * End OF SLAED5
188 *
189  END