LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dlae2.f
Go to the documentation of this file.
1*> \brief \b DLAE2 computes the eigenvalues of a 2-by-2 symmetric matrix.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DLAE2 + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlae2.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlae2.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlae2.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DLAE2( A, B, C, RT1, RT2 )
20*
21* .. Scalar Arguments ..
22* DOUBLE PRECISION A, B, C, RT1, RT2
23* ..
24*
25*
26*> \par Purpose:
27* =============
28*>
29*> \verbatim
30*>
31*> DLAE2 computes the eigenvalues of a 2-by-2 symmetric matrix
32*> [ A B ]
33*> [ B C ].
34*> On return, RT1 is the eigenvalue of larger absolute value, and RT2
35*> is the eigenvalue of smaller absolute value.
36*> \endverbatim
37*
38* Arguments:
39* ==========
40*
41*> \param[in] A
42*> \verbatim
43*> A is DOUBLE PRECISION
44*> The (1,1) element of the 2-by-2 matrix.
45*> \endverbatim
46*>
47*> \param[in] B
48*> \verbatim
49*> B is DOUBLE PRECISION
50*> The (1,2) and (2,1) elements of the 2-by-2 matrix.
51*> \endverbatim
52*>
53*> \param[in] C
54*> \verbatim
55*> C is DOUBLE PRECISION
56*> The (2,2) element of the 2-by-2 matrix.
57*> \endverbatim
58*>
59*> \param[out] RT1
60*> \verbatim
61*> RT1 is DOUBLE PRECISION
62*> The eigenvalue of larger absolute value.
63*> \endverbatim
64*>
65*> \param[out] RT2
66*> \verbatim
67*> RT2 is DOUBLE PRECISION
68*> The eigenvalue of smaller absolute value.
69*> \endverbatim
70*
71* Authors:
72* ========
73*
74*> \author Univ. of Tennessee
75*> \author Univ. of California Berkeley
76*> \author Univ. of Colorado Denver
77*> \author NAG Ltd.
78*
79*> \ingroup lae2
80*
81*> \par Further Details:
82* =====================
83*>
84*> \verbatim
85*>
86*> RT1 is accurate to a few ulps barring over/underflow.
87*>
88*> RT2 may be inaccurate if there is massive cancellation in the
89*> determinant A*C-B*B; higher precision or correctly rounded or
90*> correctly truncated arithmetic would be needed to compute RT2
91*> accurately in all cases.
92*>
93*> Overflow is possible only if RT1 is within a factor of 5 of overflow.
94*> Underflow is harmless if the input data is 0 or exceeds
95*> underflow_threshold / macheps.
96*> \endverbatim
97*>
98* =====================================================================
99 SUBROUTINE dlae2( A, B, C, RT1, RT2 )
100*
101* -- LAPACK auxiliary routine --
102* -- LAPACK is a software package provided by Univ. of Tennessee, --
103* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
104*
105* .. Scalar Arguments ..
106 DOUBLE PRECISION A, B, C, RT1, RT2
107* ..
108*
109* =====================================================================
110*
111* .. Parameters ..
112 DOUBLE PRECISION ONE
113 parameter( one = 1.0d0 )
114 DOUBLE PRECISION TWO
115 parameter( two = 2.0d0 )
116 DOUBLE PRECISION ZERO
117 parameter( zero = 0.0d0 )
118 DOUBLE PRECISION HALF
119 parameter( half = 0.5d0 )
120* ..
121* .. Local Scalars ..
122 DOUBLE PRECISION AB, ACMN, ACMX, ADF, DF, RT, SM, TB
123* ..
124* .. Intrinsic Functions ..
125 INTRINSIC abs, sqrt
126* ..
127* .. Executable Statements ..
128*
129* Compute the eigenvalues
130*
131 sm = a + c
132 df = a - c
133 adf = abs( df )
134 tb = b + b
135 ab = abs( tb )
136 IF( abs( a ).GT.abs( c ) ) THEN
137 acmx = a
138 acmn = c
139 ELSE
140 acmx = c
141 acmn = a
142 END IF
143 IF( adf.GT.ab ) THEN
144 rt = adf*sqrt( one+( ab / adf )**2 )
145 ELSE IF( adf.LT.ab ) THEN
146 rt = ab*sqrt( one+( adf / ab )**2 )
147 ELSE
148*
149* Includes case AB=ADF=0
150*
151 rt = ab*sqrt( two )
152 END IF
153 IF( sm.LT.zero ) THEN
154 rt1 = half*( sm-rt )
155*
156* Order of execution important.
157* To get fully accurate smaller eigenvalue,
158* next line needs to be executed in higher precision.
159*
160 rt2 = ( acmx / rt1 )*acmn - ( b / rt1 )*b
161 ELSE IF( sm.GT.zero ) THEN
162 rt1 = half*( sm+rt )
163*
164* Order of execution important.
165* To get fully accurate smaller eigenvalue,
166* next line needs to be executed in higher precision.
167*
168 rt2 = ( acmx / rt1 )*acmn - ( b / rt1 )*b
169 ELSE
170*
171* Includes case RT1 = RT2 = 0
172*
173 rt1 = half*rt
174 rt2 = -half*rt
175 END IF
176 RETURN
177*
178* End of DLAE2
179*
180 END
subroutine dlae2(a, b, c, rt1, rt2)
DLAE2 computes the eigenvalues of a 2-by-2 symmetric matrix.
Definition dlae2.f:100