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