1 *> \brief \b CLAESY computes the eigenvalues and eigenvectors of a 2-by-2 complex symmetric matrix.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CLAESY + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/claesy.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/claesy.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/claesy.f">
21 * SUBROUTINE CLAESY( A, B, C, RT1, RT2, EVSCAL, CS1, SN1 )
23 * .. Scalar Arguments ..
24 * COMPLEX A, B, C, CS1, EVSCAL, RT1, RT2, SN1
33 *> CLAESY computes the eigendecomposition of a 2-by-2 symmetric matrix
34 *> ( ( A, B );( B, C ) )
35 *> provided the norm of the matrix of eigenvectors is larger than
36 *> some threshold value.
38 *> RT1 is the eigenvalue of larger absolute value, and RT2 of
39 *> smaller absolute value. If the eigenvectors are computed, then
40 *> on return ( CS1, SN1 ) is the unit eigenvector for RT1, hence
42 *> [ CS1 SN1 ] . [ A B ] . [ CS1 -SN1 ] = [ RT1 0 ]
43 *> [ -SN1 CS1 ] [ B C ] [ SN1 CS1 ] [ 0 RT2 ]
52 *> The ( 1, 1 ) element of input matrix.
58 *> The ( 1, 2 ) element of input matrix. The ( 2, 1 ) element
59 *> is also given by B, since the 2-by-2 matrix is symmetric.
65 *> The ( 2, 2 ) element of input matrix.
71 *> The eigenvalue of larger modulus.
77 *> The eigenvalue of smaller modulus.
83 *> The complex value by which the eigenvector matrix was scaled
84 *> to make it orthonormal. If EVSCAL is zero, the eigenvectors
85 *> were not computed. This means one of two things: the 2-by-2
86 *> matrix could not be diagonalized, or the norm of the matrix
87 *> of eigenvectors before scaling was larger than the threshold
88 *> value THRESH (set below).
99 *> If EVSCAL .NE. 0, ( CS1, SN1 ) is the unit right eigenvector
106 *> \author Univ. of Tennessee
107 *> \author Univ. of California Berkeley
108 *> \author Univ. of Colorado Denver
111 *> \date September 2012
113 *> \ingroup complexSYauxiliary
115 * =====================================================================
116 SUBROUTINE CLAESY( A, B, C, RT1, RT2, EVSCAL, CS1, SN1 )
118 * -- LAPACK auxiliary routine (version 3.4.2) --
119 * -- LAPACK is a software package provided by Univ. of Tennessee, --
120 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
123 * .. Scalar Arguments ..
124 COMPLEX A, B, C, CS1, EVSCAL, RT1, RT2, SN1
127 * =====================================================================
131 PARAMETER ( ZERO = 0.0E0 )
133 PARAMETER ( ONE = 1.0E0 )
135 PARAMETER ( CONE = ( 1.0E0, 0.0E0 ) )
137 PARAMETER ( HALF = 0.5E0 )
139 PARAMETER ( THRESH = 0.1E0 )
141 * .. Local Scalars ..
142 REAL BABS, EVNORM, TABS, Z
145 * .. Intrinsic Functions ..
146 INTRINSIC ABS, MAX, SQRT
148 * .. Executable Statements ..
151 * Special case: The matrix is actually diagonal.
152 * To avoid divide by zero later, we treat this case separately.
154 IF( ABS( B ).EQ.ZERO ) THEN
157 IF( ABS( RT1 ).LT.ABS( RT2 ) ) THEN
169 * Compute the eigenvalues and eigenvectors.
170 * The characteristic equation is
171 * lambda **2 - (A+C) lambda + (A*C - B*B)
172 * and we solve it using the quadratic formula.
177 * Take the square root carefully to avoid over/under flow.
181 Z = MAX( BABS, TABS )
183 $ T = Z*SQRT( ( T / Z )**2+( B / Z )**2 )
185 * Compute the two eigenvalues. RT1 and RT2 are exchanged
186 * if necessary so that RT1 will have the greater magnitude.
190 IF( ABS( RT1 ).LT.ABS( RT2 ) ) THEN
196 * Choose CS1 = 1 and SN1 to satisfy the first equation, then
197 * scale the components of this eigenvector so that the matrix
198 * of eigenvectors X satisfies X * X**T = I . (No scaling is
199 * done if the norm of the eigenvalue matrix is less than THRESH.)
203 IF( TABS.GT.ONE ) THEN
204 T = TABS*SQRT( ( ONE / TABS )**2+( SN1 / TABS )**2 )
206 T = SQRT( CONE+SN1*SN1 )
209 IF( EVNORM.GE.THRESH ) THEN