1 *> \brief \b ZLAEV2 computes the eigenvalues and eigenvectors of a 2-by-2 symmetric/Hermitian matrix.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download ZLAEV2 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlaev2.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlaev2.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaev2.f">
21 * SUBROUTINE ZLAEV2( A, B, C, RT1, RT2, CS1, SN1 )
23 * .. Scalar Arguments ..
24 * DOUBLE PRECISION CS1, RT1, RT2
25 * COMPLEX*16 A, B, C, SN1
34 *> ZLAEV2 computes the eigendecomposition of a 2-by-2 Hermitian matrix
37 *> On return, RT1 is the eigenvalue of larger absolute value, RT2 is the
38 *> eigenvalue of smaller absolute value, and (CS1,SN1) is the unit right
39 *> eigenvector for RT1, giving the decomposition
41 *> [ CS1 CONJG(SN1) ] [ A B ] [ CS1 -CONJG(SN1) ] = [ RT1 0 ]
42 *> [-SN1 CS1 ] [ CONJG(B) C ] [ SN1 CS1 ] [ 0 RT2 ].
51 *> The (1,1) element of the 2-by-2 matrix.
57 *> The (1,2) element and the conjugate of the (2,1) element of
64 *> The (2,2) element of the 2-by-2 matrix.
69 *> RT1 is DOUBLE PRECISION
70 *> The eigenvalue of larger absolute value.
75 *> RT2 is DOUBLE PRECISION
76 *> The eigenvalue of smaller absolute value.
81 *> CS1 is DOUBLE PRECISION
87 *> The vector (CS1, SN1) is a unit right eigenvector for RT1.
93 *> \author Univ. of Tennessee
94 *> \author Univ. of California Berkeley
95 *> \author Univ. of Colorado Denver
98 *> \date September 2012
100 *> \ingroup complex16OTHERauxiliary
102 *> \par Further Details:
103 * =====================
107 *> RT1 is accurate to a few ulps barring over/underflow.
109 *> RT2 may be inaccurate if there is massive cancellation in the
110 *> determinant A*C-B*B; higher precision or correctly rounded or
111 *> correctly truncated arithmetic would be needed to compute RT2
112 *> accurately in all cases.
114 *> CS1 and SN1 are accurate to a few ulps barring over/underflow.
116 *> Overflow is possible only if RT1 is within a factor of 5 of overflow.
117 *> Underflow is harmless if the input data is 0 or exceeds
118 *> underflow_threshold / macheps.
121 * =====================================================================
122 SUBROUTINE ZLAEV2( A, B, C, RT1, RT2, CS1, SN1 )
124 * -- LAPACK auxiliary routine (version 3.4.2) --
125 * -- LAPACK is a software package provided by Univ. of Tennessee, --
126 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
129 * .. Scalar Arguments ..
130 DOUBLE PRECISION CS1, RT1, RT2
131 COMPLEX*16 A, B, C, SN1
134 * =====================================================================
137 DOUBLE PRECISION ZERO
138 PARAMETER ( ZERO = 0.0D0 )
140 PARAMETER ( ONE = 1.0D0 )
142 * .. Local Scalars ..
146 * .. External Subroutines ..
149 * .. Intrinsic Functions ..
150 INTRINSIC ABS, DBLE, DCONJG
152 * .. Executable Statements ..
154 IF( ABS( B ).EQ.ZERO ) THEN
157 W = DCONJG( B ) / ABS( B )
159 CALL DLAEV2( DBLE( A ), ABS( B ), DBLE( C ), RT1, RT2, CS1, T )