502dbfa814613548b88e005d3b073d37b9743fe3
[platform/upstream/lapack.git] / SRC / zlaev2.f
1 *> \brief \b ZLAEV2 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 *> \htmlonly
9 *> Download ZLAEV2 + dependencies 
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlaev2.f"> 
11 *> [TGZ]</a> 
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlaev2.f"> 
13 *> [ZIP]</a> 
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaev2.f"> 
15 *> [TXT]</a>
16 *> \endhtmlonly 
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       SUBROUTINE ZLAEV2( A, B, C, RT1, RT2, CS1, SN1 )
22
23 *       .. Scalar Arguments ..
24 *       DOUBLE PRECISION   CS1, RT1, RT2
25 *       COMPLEX*16         A, B, C, SN1
26 *       ..
27 *  
28 *
29 *> \par Purpose:
30 *  =============
31 *>
32 *> \verbatim
33 *>
34 *> ZLAEV2 computes the eigendecomposition of a 2-by-2 Hermitian matrix
35 *>    [  A         B  ]
36 *>    [  CONJG(B)  C  ].
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
40 *>
41 *> [ CS1  CONJG(SN1) ] [    A     B ] [ CS1 -CONJG(SN1) ] = [ RT1  0  ]
42 *> [-SN1     CS1     ] [ CONJG(B) C ] [ SN1     CS1     ]   [  0  RT2 ].
43 *> \endverbatim
44 *
45 *  Arguments:
46 *  ==========
47 *
48 *> \param[in] A
49 *> \verbatim
50 *>          A is COMPLEX*16
51 *>         The (1,1) element of the 2-by-2 matrix.
52 *> \endverbatim
53 *>
54 *> \param[in] B
55 *> \verbatim
56 *>          B is COMPLEX*16
57 *>         The (1,2) element and the conjugate of the (2,1) element of
58 *>         the 2-by-2 matrix.
59 *> \endverbatim
60 *>
61 *> \param[in] C
62 *> \verbatim
63 *>          C is COMPLEX*16
64 *>         The (2,2) element of the 2-by-2 matrix.
65 *> \endverbatim
66 *>
67 *> \param[out] RT1
68 *> \verbatim
69 *>          RT1 is DOUBLE PRECISION
70 *>         The eigenvalue of larger absolute value.
71 *> \endverbatim
72 *>
73 *> \param[out] RT2
74 *> \verbatim
75 *>          RT2 is DOUBLE PRECISION
76 *>         The eigenvalue of smaller absolute value.
77 *> \endverbatim
78 *>
79 *> \param[out] CS1
80 *> \verbatim
81 *>          CS1 is DOUBLE PRECISION
82 *> \endverbatim
83 *>
84 *> \param[out] SN1
85 *> \verbatim
86 *>          SN1 is COMPLEX*16
87 *>         The vector (CS1, SN1) is a unit right eigenvector for RT1.
88 *> \endverbatim
89 *
90 *  Authors:
91 *  ========
92 *
93 *> \author Univ. of Tennessee 
94 *> \author Univ. of California Berkeley 
95 *> \author Univ. of Colorado Denver 
96 *> \author NAG Ltd. 
97 *
98 *> \date September 2012
99 *
100 *> \ingroup complex16OTHERauxiliary
101 *
102 *> \par Further Details:
103 *  =====================
104 *>
105 *> \verbatim
106 *>
107 *>  RT1 is accurate to a few ulps barring over/underflow.
108 *>
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.
113 *>
114 *>  CS1 and SN1 are accurate to a few ulps barring over/underflow.
115 *>
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.
119 *> \endverbatim
120 *>
121 *  =====================================================================
122       SUBROUTINE ZLAEV2( A, B, C, RT1, RT2, CS1, SN1 )
123 *
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..--
127 *     September 2012
128 *
129 *     .. Scalar Arguments ..
130       DOUBLE PRECISION   CS1, RT1, RT2
131       COMPLEX*16         A, B, C, SN1
132 *     ..
133 *
134 * =====================================================================
135 *
136 *     .. Parameters ..
137       DOUBLE PRECISION   ZERO
138       PARAMETER          ( ZERO = 0.0D0 )
139       DOUBLE PRECISION   ONE
140       PARAMETER          ( ONE = 1.0D0 )
141 *     ..
142 *     .. Local Scalars ..
143       DOUBLE PRECISION   T
144       COMPLEX*16         W
145 *     ..
146 *     .. External Subroutines ..
147       EXTERNAL           DLAEV2
148 *     ..
149 *     .. Intrinsic Functions ..
150       INTRINSIC          ABS, DBLE, DCONJG
151 *     ..
152 *     .. Executable Statements ..
153 *
154       IF( ABS( B ).EQ.ZERO ) THEN
155          W = ONE
156       ELSE
157          W = DCONJG( B ) / ABS( B )
158       END IF
159       CALL DLAEV2( DBLE( A ), ABS( B ), DBLE( C ), RT1, RT2, CS1, T )
160       SN1 = W*T
161       RETURN
162 *
163 *     End of ZLAEV2
164 *
165       END