LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
claev2.f
Go to the documentation of this file.
1*> \brief \b CLAEV2 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 CLAEV2 + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/claev2.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/claev2.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/claev2.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CLAEV2( A, B, C, RT1, RT2, CS1, SN1 )
20*
21* .. Scalar Arguments ..
22* REAL CS1, RT1, RT2
23* COMPLEX A, B, C, SN1
24* ..
25*
26*
27*> \par Purpose:
28* =============
29*>
30*> \verbatim
31*>
32*> CLAEV2 computes the eigendecomposition of a 2-by-2 Hermitian matrix
33*> [ A B ]
34*> [ CONJG(B) C ].
35*> On return, RT1 is the eigenvalue of larger absolute value, RT2 is the
36*> eigenvalue of smaller absolute value, and (CS1,SN1) is the unit right
37*> eigenvector for RT1, giving the decomposition
38*>
39*> [ CS1 CONJG(SN1) ] [ A B ] [ CS1 -CONJG(SN1) ] = [ RT1 0 ]
40*> [-SN1 CS1 ] [ CONJG(B) C ] [ SN1 CS1 ] [ 0 RT2 ].
41*> \endverbatim
42*
43* Arguments:
44* ==========
45*
46*> \param[in] A
47*> \verbatim
48*> A is COMPLEX
49*> The (1,1) element of the 2-by-2 matrix.
50*> \endverbatim
51*>
52*> \param[in] B
53*> \verbatim
54*> B is COMPLEX
55*> The (1,2) element and the conjugate of the (2,1) element of
56*> the 2-by-2 matrix.
57*> \endverbatim
58*>
59*> \param[in] C
60*> \verbatim
61*> C is COMPLEX
62*> The (2,2) element of the 2-by-2 matrix.
63*> \endverbatim
64*>
65*> \param[out] RT1
66*> \verbatim
67*> RT1 is REAL
68*> The eigenvalue of larger absolute value.
69*> \endverbatim
70*>
71*> \param[out] RT2
72*> \verbatim
73*> RT2 is REAL
74*> The eigenvalue of smaller absolute value.
75*> \endverbatim
76*>
77*> \param[out] CS1
78*> \verbatim
79*> CS1 is REAL
80*> \endverbatim
81*>
82*> \param[out] SN1
83*> \verbatim
84*> SN1 is COMPLEX
85*> The vector (CS1, SN1) is a unit right eigenvector for RT1.
86*> \endverbatim
87*
88* Authors:
89* ========
90*
91*> \author Univ. of Tennessee
92*> \author Univ. of California Berkeley
93*> \author Univ. of Colorado Denver
94*> \author NAG Ltd.
95*
96*> \ingroup laev2
97*
98*> \par Further Details:
99* =====================
100*>
101*> \verbatim
102*>
103*> RT1 is accurate to a few ulps barring over/underflow.
104*>
105*> RT2 may be inaccurate if there is massive cancellation in the
106*> determinant A*C-B*B; higher precision or correctly rounded or
107*> correctly truncated arithmetic would be needed to compute RT2
108*> accurately in all cases.
109*>
110*> CS1 and SN1 are accurate to a few ulps barring over/underflow.
111*>
112*> Overflow is possible only if RT1 is within a factor of 5 of overflow.
113*> Underflow is harmless if the input data is 0 or exceeds
114*> underflow_threshold / macheps.
115*> \endverbatim
116*>
117* =====================================================================
118 SUBROUTINE claev2( A, B, C, RT1, RT2, CS1, SN1 )
119*
120* -- LAPACK auxiliary routine --
121* -- LAPACK is a software package provided by Univ. of Tennessee, --
122* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
123*
124* .. Scalar Arguments ..
125 REAL CS1, RT1, RT2
126 COMPLEX A, B, C, SN1
127* ..
128*
129* =====================================================================
130*
131* .. Parameters ..
132 REAL ZERO
133 parameter( zero = 0.0e0 )
134 REAL ONE
135 parameter( one = 1.0e0 )
136* ..
137* .. Local Scalars ..
138 REAL T
139 COMPLEX W
140* ..
141* .. External Subroutines ..
142 EXTERNAL slaev2
143* ..
144* .. Intrinsic Functions ..
145 INTRINSIC abs, conjg, real
146* ..
147* .. Executable Statements ..
148*
149 IF( abs( b ).EQ.zero ) THEN
150 w = one
151 ELSE
152 w = conjg( b ) / abs( b )
153 END IF
154 CALL slaev2( real( a ), abs( b ), real( c ), rt1, rt2, cs1, t )
155 sn1 = w*t
156 RETURN
157*
158* End of CLAEV2
159*
160 END
subroutine claev2(a, b, c, rt1, rt2, cs1, sn1)
CLAEV2 computes the eigenvalues and eigenvectors of a 2-by-2 symmetric/Hermitian matrix.
Definition claev2.f:119
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