LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
claesy.f
Go to the documentation of this file.
1*> \brief \b CLAESY computes the eigenvalues and eigenvectors of a 2-by-2 complex symmetric matrix.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download CLAESY + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/claesy.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/claesy.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/claesy.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CLAESY( A, B, C, RT1, RT2, EVSCAL, CS1, SN1 )
20*
21* .. Scalar Arguments ..
22* COMPLEX A, B, C, CS1, EVSCAL, RT1, RT2, SN1
23* ..
24*
25*
26*> \par Purpose:
27* =============
28*>
29*> \verbatim
30*>
31*> CLAESY computes the eigendecomposition of a 2-by-2 symmetric matrix
32*> ( ( A, B );( B, C ) )
33*> provided the norm of the matrix of eigenvectors is larger than
34*> some threshold value.
35*>
36*> RT1 is the eigenvalue of larger absolute value, and RT2 of
37*> smaller absolute value. If the eigenvectors are computed, then
38*> on return ( CS1, SN1 ) is the unit eigenvector for RT1, hence
39*>
40*> [ CS1 SN1 ] . [ A B ] . [ CS1 -SN1 ] = [ RT1 0 ]
41*> [ -SN1 CS1 ] [ B C ] [ SN1 CS1 ] [ 0 RT2 ]
42*> \endverbatim
43*
44* Arguments:
45* ==========
46*
47*> \param[in] A
48*> \verbatim
49*> A is COMPLEX
50*> The ( 1, 1 ) element of input matrix.
51*> \endverbatim
52*>
53*> \param[in] B
54*> \verbatim
55*> B is COMPLEX
56*> The ( 1, 2 ) element of input matrix. The ( 2, 1 ) element
57*> is also given by B, since the 2-by-2 matrix is symmetric.
58*> \endverbatim
59*>
60*> \param[in] C
61*> \verbatim
62*> C is COMPLEX
63*> The ( 2, 2 ) element of input matrix.
64*> \endverbatim
65*>
66*> \param[out] RT1
67*> \verbatim
68*> RT1 is COMPLEX
69*> The eigenvalue of larger modulus.
70*> \endverbatim
71*>
72*> \param[out] RT2
73*> \verbatim
74*> RT2 is COMPLEX
75*> The eigenvalue of smaller modulus.
76*> \endverbatim
77*>
78*> \param[out] EVSCAL
79*> \verbatim
80*> EVSCAL is COMPLEX
81*> The complex value by which the eigenvector matrix was scaled
82*> to make it orthonormal. If EVSCAL is zero, the eigenvectors
83*> were not computed. This means one of two things: the 2-by-2
84*> matrix could not be diagonalized, or the norm of the matrix
85*> of eigenvectors before scaling was larger than the threshold
86*> value THRESH (set below).
87*> \endverbatim
88*>
89*> \param[out] CS1
90*> \verbatim
91*> CS1 is COMPLEX
92*> \endverbatim
93*>
94*> \param[out] SN1
95*> \verbatim
96*> SN1 is COMPLEX
97*> If EVSCAL .NE. 0, ( CS1, SN1 ) is the unit right eigenvector
98*> for RT1.
99*> \endverbatim
100*
101* Authors:
102* ========
103*
104*> \author Univ. of Tennessee
105*> \author Univ. of California Berkeley
106*> \author Univ. of Colorado Denver
107*> \author NAG Ltd.
108*
109*> \ingroup laesy
110*
111* =====================================================================
112 SUBROUTINE claesy( A, B, C, RT1, RT2, EVSCAL, CS1, SN1 )
113*
114* -- LAPACK auxiliary routine --
115* -- LAPACK is a software package provided by Univ. of Tennessee, --
116* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
117*
118* .. Scalar Arguments ..
119 COMPLEX A, B, C, CS1, EVSCAL, RT1, RT2, SN1
120* ..
121*
122* =====================================================================
123*
124* .. Parameters ..
125 REAL ZERO
126 parameter( zero = 0.0e0 )
127 REAL ONE
128 parameter( one = 1.0e0 )
129 COMPLEX CONE
130 parameter( cone = ( 1.0e0, 0.0e0 ) )
131 REAL HALF
132 parameter( half = 0.5e0 )
133 REAL THRESH
134 parameter( thresh = 0.1e0 )
135* ..
136* .. Local Scalars ..
137 REAL BABS, EVNORM, TABS, Z
138 COMPLEX S, T, TMP
139* ..
140* .. Intrinsic Functions ..
141 INTRINSIC abs, max, sqrt
142* ..
143* .. Executable Statements ..
144*
145*
146* Special case: The matrix is actually diagonal.
147* To avoid divide by zero later, we treat this case separately.
148*
149 IF( abs( b ).EQ.zero ) THEN
150 rt1 = a
151 rt2 = c
152 IF( abs( rt1 ).LT.abs( rt2 ) ) THEN
153 tmp = rt1
154 rt1 = rt2
155 rt2 = tmp
156 cs1 = zero
157 sn1 = one
158 ELSE
159 cs1 = one
160 sn1 = zero
161 END IF
162 ELSE
163*
164* Compute the eigenvalues and eigenvectors.
165* The characteristic equation is
166* lambda **2 - (A+C) lambda + (A*C - B*B)
167* and we solve it using the quadratic formula.
168*
169 s = ( a+c )*half
170 t = ( a-c )*half
171*
172* Take the square root carefully to avoid over/under flow.
173*
174 babs = abs( b )
175 tabs = abs( t )
176 z = max( babs, tabs )
177 IF( z.GT.zero )
178 $ t = z*sqrt( ( t / z )**2+( b / z )**2 )
179*
180* Compute the two eigenvalues. RT1 and RT2 are exchanged
181* if necessary so that RT1 will have the greater magnitude.
182*
183 rt1 = s + t
184 rt2 = s - t
185 IF( abs( rt1 ).LT.abs( rt2 ) ) THEN
186 tmp = rt1
187 rt1 = rt2
188 rt2 = tmp
189 END IF
190*
191* Choose CS1 = 1 and SN1 to satisfy the first equation, then
192* scale the components of this eigenvector so that the matrix
193* of eigenvectors X satisfies X * X**T = I . (No scaling is
194* done if the norm of the eigenvalue matrix is less than THRESH.)
195*
196 sn1 = ( rt1-a ) / b
197 tabs = abs( sn1 )
198 IF( tabs.GT.one ) THEN
199 t = tabs*sqrt( ( one / tabs )**2+( sn1 / tabs )**2 )
200 ELSE
201 t = sqrt( cone+sn1*sn1 )
202 END IF
203 evnorm = abs( t )
204 IF( evnorm.GE.thresh ) THEN
205 evscal = cone / t
206 cs1 = evscal
207 sn1 = sn1*evscal
208 ELSE
209 evscal = zero
210 END IF
211 END IF
212 RETURN
213*
214* End of CLAESY
215*
216 END
subroutine claesy(a, b, c, rt1, rt2, evscal, cs1, sn1)
CLAESY computes the eigenvalues and eigenvectors of a 2-by-2 complex symmetric matrix.
Definition claesy.f:113