001:       SUBROUTINE DLAED5( I, D, Z, DELTA, RHO, DLAM )
002: *
003: *  -- LAPACK routine (version 3.2) --
004: *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
005: *     November 2006
006: *
007: *     .. Scalar Arguments ..
008:       INTEGER            I
009:       DOUBLE PRECISION   DLAM, RHO
010: *     ..
011: *     .. Array Arguments ..
012:       DOUBLE PRECISION   D( 2 ), DELTA( 2 ), Z( 2 )
013: *     ..
014: *
015: *  Purpose
016: *  =======
017: *
018: *  This subroutine computes the I-th eigenvalue of a symmetric rank-one
019: *  modification of a 2-by-2 diagonal matrix
020: *
021: *             diag( D )  +  RHO *  Z * transpose(Z) .
022: *
023: *  The diagonal elements in the array D are assumed to satisfy
024: *
025: *             D(i) < D(j)  for  i < j .
026: *
027: *  We also assume RHO > 0 and that the Euclidean norm of the vector
028: *  Z is one.
029: *
030: *  Arguments
031: *  =========
032: *
033: *  I      (input) INTEGER
034: *         The index of the eigenvalue to be computed.  I = 1 or I = 2.
035: *
036: *  D      (input) DOUBLE PRECISION array, dimension (2)
037: *         The original eigenvalues.  We assume D(1) < D(2).
038: *
039: *  Z      (input) DOUBLE PRECISION array, dimension (2)
040: *         The components of the updating vector.
041: *
042: *  DELTA  (output) DOUBLE PRECISION array, dimension (2)
043: *         The vector DELTA contains the information necessary
044: *         to construct the eigenvectors.
045: *
046: *  RHO    (input) DOUBLE PRECISION
047: *         The scalar in the symmetric updating formula.
048: *
049: *  DLAM   (output) DOUBLE PRECISION
050: *         The computed lambda_I, the I-th updated eigenvalue.
051: *
052: *  Further Details
053: *  ===============
054: *
055: *  Based on contributions by
056: *     Ren-Cang Li, Computer Science Division, University of California
057: *     at Berkeley, USA
058: *
059: *  =====================================================================
060: *
061: *     .. Parameters ..
062:       DOUBLE PRECISION   ZERO, ONE, TWO, FOUR
063:       PARAMETER          ( ZERO = 0.0D0, ONE = 1.0D0, TWO = 2.0D0,
064:      $                   FOUR = 4.0D0 )
065: *     ..
066: *     .. Local Scalars ..
067:       DOUBLE PRECISION   B, C, DEL, TAU, TEMP, W
068: *     ..
069: *     .. Intrinsic Functions ..
070:       INTRINSIC          ABS, SQRT
071: *     ..
072: *     .. Executable Statements ..
073: *
074:       DEL = D( 2 ) - D( 1 )
075:       IF( I.EQ.1 ) THEN
076:          W = ONE + TWO*RHO*( Z( 2 )*Z( 2 )-Z( 1 )*Z( 1 ) ) / DEL
077:          IF( W.GT.ZERO ) THEN
078:             B = DEL + RHO*( Z( 1 )*Z( 1 )+Z( 2 )*Z( 2 ) )
079:             C = RHO*Z( 1 )*Z( 1 )*DEL
080: *
081: *           B > ZERO, always
082: *
083:             TAU = TWO*C / ( B+SQRT( ABS( B*B-FOUR*C ) ) )
084:             DLAM = D( 1 ) + TAU
085:             DELTA( 1 ) = -Z( 1 ) / TAU
086:             DELTA( 2 ) = Z( 2 ) / ( DEL-TAU )
087:          ELSE
088:             B = -DEL + RHO*( Z( 1 )*Z( 1 )+Z( 2 )*Z( 2 ) )
089:             C = RHO*Z( 2 )*Z( 2 )*DEL
090:             IF( B.GT.ZERO ) THEN
091:                TAU = -TWO*C / ( B+SQRT( B*B+FOUR*C ) )
092:             ELSE
093:                TAU = ( B-SQRT( B*B+FOUR*C ) ) / TWO
094:             END IF
095:             DLAM = D( 2 ) + TAU
096:             DELTA( 1 ) = -Z( 1 ) / ( DEL+TAU )
097:             DELTA( 2 ) = -Z( 2 ) / TAU
098:          END IF
099:          TEMP = SQRT( DELTA( 1 )*DELTA( 1 )+DELTA( 2 )*DELTA( 2 ) )
100:          DELTA( 1 ) = DELTA( 1 ) / TEMP
101:          DELTA( 2 ) = DELTA( 2 ) / TEMP
102:       ELSE
103: *
104: *     Now I=2
105: *
106:          B = -DEL + RHO*( Z( 1 )*Z( 1 )+Z( 2 )*Z( 2 ) )
107:          C = RHO*Z( 2 )*Z( 2 )*DEL
108:          IF( B.GT.ZERO ) THEN
109:             TAU = ( B+SQRT( B*B+FOUR*C ) ) / TWO
110:          ELSE
111:             TAU = TWO*C / ( -B+SQRT( B*B+FOUR*C ) )
112:          END IF
113:          DLAM = D( 2 ) + TAU
114:          DELTA( 1 ) = -Z( 1 ) / ( DEL+TAU )
115:          DELTA( 2 ) = -Z( 2 ) / TAU
116:          TEMP = SQRT( DELTA( 1 )*DELTA( 1 )+DELTA( 2 )*DELTA( 2 ) )
117:          DELTA( 1 ) = DELTA( 1 ) / TEMP
118:          DELTA( 2 ) = DELTA( 2 ) / TEMP
119:       END IF
120:       RETURN
121: *
122: *     End OF DLAED5
123: *
124:       END
125: