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