001:       SUBROUTINE ZLAESY( A, B, C, RT1, RT2, EVSCAL, CS1, SN1 )
002: *
003: *  -- LAPACK auxiliary routine (version 3.2) --
004: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
005: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
006: *     November 2006
007: *
008: *     .. Scalar Arguments ..
009:       COMPLEX*16         A, B, C, CS1, EVSCAL, RT1, RT2, SN1
010: *     ..
011: *
012: *  Purpose
013: *  =======
014: *
015: *  ZLAESY computes the eigendecomposition of a 2-by-2 symmetric matrix
016: *     ( ( A, B );( B, C ) )
017: *  provided the norm of the matrix of eigenvectors is larger than
018: *  some threshold value.
019: *
020: *  RT1 is the eigenvalue of larger absolute value, and RT2 of
021: *  smaller absolute value.  If the eigenvectors are computed, then
022: *  on return ( CS1, SN1 ) is the unit eigenvector for RT1, hence
023: *
024: *  [  CS1     SN1   ] . [ A  B ] . [ CS1    -SN1   ] = [ RT1  0  ]
025: *  [ -SN1     CS1   ]   [ B  C ]   [ SN1     CS1   ]   [  0  RT2 ]
026: *
027: *  Arguments
028: *  =========
029: *
030: *  A       (input) COMPLEX*16
031: *          The ( 1, 1 ) element of input matrix.
032: *
033: *  B       (input) COMPLEX*16
034: *          The ( 1, 2 ) element of input matrix.  The ( 2, 1 ) element
035: *          is also given by B, since the 2-by-2 matrix is symmetric.
036: *
037: *  C       (input) COMPLEX*16
038: *          The ( 2, 2 ) element of input matrix.
039: *
040: *  RT1     (output) COMPLEX*16
041: *          The eigenvalue of larger modulus.
042: *
043: *  RT2     (output) COMPLEX*16
044: *          The eigenvalue of smaller modulus.
045: *
046: *  EVSCAL  (output) COMPLEX*16
047: *          The complex value by which the eigenvector matrix was scaled
048: *          to make it orthonormal.  If EVSCAL is zero, the eigenvectors
049: *          were not computed.  This means one of two things:  the 2-by-2
050: *          matrix could not be diagonalized, or the norm of the matrix
051: *          of eigenvectors before scaling was larger than the threshold
052: *          value THRESH (set below).
053: *
054: *  CS1     (output) COMPLEX*16
055: *  SN1     (output) COMPLEX*16
056: *          If EVSCAL .NE. 0,  ( CS1, SN1 ) is the unit right eigenvector
057: *          for RT1.
058: *
059: * =====================================================================
060: *
061: *     .. Parameters ..
062:       DOUBLE PRECISION   ZERO
063:       PARAMETER          ( ZERO = 0.0D0 )
064:       DOUBLE PRECISION   ONE
065:       PARAMETER          ( ONE = 1.0D0 )
066:       COMPLEX*16         CONE
067:       PARAMETER          ( CONE = ( 1.0D0, 0.0D0 ) )
068:       DOUBLE PRECISION   HALF
069:       PARAMETER          ( HALF = 0.5D0 )
070:       DOUBLE PRECISION   THRESH
071:       PARAMETER          ( THRESH = 0.1D0 )
072: *     ..
073: *     .. Local Scalars ..
074:       DOUBLE PRECISION   BABS, EVNORM, TABS, Z
075:       COMPLEX*16         S, T, TMP
076: *     ..
077: *     .. Intrinsic Functions ..
078:       INTRINSIC          ABS, MAX, SQRT
079: *     ..
080: *     .. Executable Statements ..
081: *
082: *
083: *     Special case:  The matrix is actually diagonal.
084: *     To avoid divide by zero later, we treat this case separately.
085: *
086:       IF( ABS( B ).EQ.ZERO ) THEN
087:          RT1 = A
088:          RT2 = C
089:          IF( ABS( RT1 ).LT.ABS( RT2 ) ) THEN
090:             TMP = RT1
091:             RT1 = RT2
092:             RT2 = TMP
093:             CS1 = ZERO
094:             SN1 = ONE
095:          ELSE
096:             CS1 = ONE
097:             SN1 = ZERO
098:          END IF
099:       ELSE
100: *
101: *        Compute the eigenvalues and eigenvectors.
102: *        The characteristic equation is
103: *           lambda **2 - (A+C) lambda + (A*C - B*B)
104: *        and we solve it using the quadratic formula.
105: *
106:          S = ( A+C )*HALF
107:          T = ( A-C )*HALF
108: *
109: *        Take the square root carefully to avoid over/under flow.
110: *
111:          BABS = ABS( B )
112:          TABS = ABS( T )
113:          Z = MAX( BABS, TABS )
114:          IF( Z.GT.ZERO )
115:      $      T = Z*SQRT( ( T / Z )**2+( B / Z )**2 )
116: *
117: *        Compute the two eigenvalues.  RT1 and RT2 are exchanged
118: *        if necessary so that RT1 will have the greater magnitude.
119: *
120:          RT1 = S + T
121:          RT2 = S - T
122:          IF( ABS( RT1 ).LT.ABS( RT2 ) ) THEN
123:             TMP = RT1
124:             RT1 = RT2
125:             RT2 = TMP
126:          END IF
127: *
128: *        Choose CS1 = 1 and SN1 to satisfy the first equation, then
129: *        scale the components of this eigenvector so that the matrix
130: *        of eigenvectors X satisfies  X * X' = I .  (No scaling is
131: *        done if the norm of the eigenvalue matrix is less than THRESH.)
132: *
133:          SN1 = ( RT1-A ) / B
134:          TABS = ABS( SN1 )
135:          IF( TABS.GT.ONE ) THEN
136:             T = TABS*SQRT( ( ONE / TABS )**2+( SN1 / TABS )**2 )
137:          ELSE
138:             T = SQRT( CONE+SN1*SN1 )
139:          END IF
140:          EVNORM = ABS( T )
141:          IF( EVNORM.GE.THRESH ) THEN
142:             EVSCAL = CONE / T
143:             CS1 = EVSCAL
144:             SN1 = SN1*EVSCAL
145:          ELSE
146:             EVSCAL = ZERO
147:          END IF
148:       END IF
149:       RETURN
150: *
151: *     End of ZLAESY
152: *
153:       END
154: