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