1       SUBROUTINE DLAG2( A, LDA, B, LDB, SAFMIN, SCALE1, SCALE2, WR1,
  2      $                  WR2, WI )
  3 *
  4 *  -- LAPACK auxiliary routine (version 3.2) --
  5 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  6 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  7 *     November 2006
  8 *
  9 *     .. Scalar Arguments ..
 10       INTEGER            LDA, LDB
 11       DOUBLE PRECISION   SAFMIN, SCALE1, SCALE2, WI, WR1, WR2
 12 *     ..
 13 *     .. Array Arguments ..
 14       DOUBLE PRECISION   A( LDA, * ), B( LDB, * )
 15 *     ..
 16 *
 17 *  Purpose
 18 *  =======
 19 *
 20 *  DLAG2 computes the eigenvalues of a 2 x 2 generalized eigenvalue
 21 *  problem  A - w B, with scaling as necessary to avoid over-/underflow.
 22 *
 23 *  The scaling factor "s" results in a modified eigenvalue equation
 24 *
 25 *      s A - w B
 26 *
 27 *  where  s  is a non-negative scaling factor chosen so that  w,  w B,
 28 *  and  s A  do not overflow and, if possible, do not underflow, either.
 29 *
 30 *  Arguments
 31 *  =========
 32 *
 33 *  A       (input) DOUBLE PRECISION array, dimension (LDA, 2)
 34 *          On entry, the 2 x 2 matrix A.  It is assumed that its 1-norm
 35 *          is less than 1/SAFMIN.  Entries less than
 36 *          sqrt(SAFMIN)*norm(A) are subject to being treated as zero.
 37 *
 38 *  LDA     (input) INTEGER
 39 *          The leading dimension of the array A.  LDA >= 2.
 40 *
 41 *  B       (input) DOUBLE PRECISION array, dimension (LDB, 2)
 42 *          On entry, the 2 x 2 upper triangular matrix B.  It is
 43 *          assumed that the one-norm of B is less than 1/SAFMIN.  The
 44 *          diagonals should be at least sqrt(SAFMIN) times the largest
 45 *          element of B (in absolute value); if a diagonal is smaller
 46 *          than that, then  +/- sqrt(SAFMIN) will be used instead of
 47 *          that diagonal.
 48 *
 49 *  LDB     (input) INTEGER
 50 *          The leading dimension of the array B.  LDB >= 2.
 51 *
 52 *  SAFMIN  (input) DOUBLE PRECISION
 53 *          The smallest positive number s.t. 1/SAFMIN does not
 54 *          overflow.  (This should always be DLAMCH('S') -- it is an
 55 *          argument in order to avoid having to call DLAMCH frequently.)
 56 *
 57 *  SCALE1  (output) DOUBLE PRECISION
 58 *          A scaling factor used to avoid over-/underflow in the
 59 *          eigenvalue equation which defines the first eigenvalue.  If
 60 *          the eigenvalues are complex, then the eigenvalues are
 61 *          ( WR1  +/-  WI i ) / SCALE1  (which may lie outside the
 62 *          exponent range of the machine), SCALE1=SCALE2, and SCALE1
 63 *          will always be positive.  If the eigenvalues are real, then
 64 *          the first (real) eigenvalue is  WR1 / SCALE1 , but this may
 65 *          overflow or underflow, and in fact, SCALE1 may be zero or
 66 *          less than the underflow threshhold if the exact eigenvalue
 67 *          is sufficiently large.
 68 *
 69 *  SCALE2  (output) DOUBLE PRECISION
 70 *          A scaling factor used to avoid over-/underflow in the
 71 *          eigenvalue equation which defines the second eigenvalue.  If
 72 *          the eigenvalues are complex, then SCALE2=SCALE1.  If the
 73 *          eigenvalues are real, then the second (real) eigenvalue is
 74 *          WR2 / SCALE2 , but this may overflow or underflow, and in
 75 *          fact, SCALE2 may be zero or less than the underflow
 76 *          threshhold if the exact eigenvalue is sufficiently large.
 77 *
 78 *  WR1     (output) DOUBLE PRECISION
 79 *          If the eigenvalue is real, then WR1 is SCALE1 times the
 80 *          eigenvalue closest to the (2,2) element of A B**(-1).  If the
 81 *          eigenvalue is complex, then WR1=WR2 is SCALE1 times the real
 82 *          part of the eigenvalues.
 83 *
 84 *  WR2     (output) DOUBLE PRECISION
 85 *          If the eigenvalue is real, then WR2 is SCALE2 times the
 86 *          other eigenvalue.  If the eigenvalue is complex, then
 87 *          WR1=WR2 is SCALE1 times the real part of the eigenvalues.
 88 *
 89 *  WI      (output) DOUBLE PRECISION
 90 *          If the eigenvalue is real, then WI is zero.  If the
 91 *          eigenvalue is complex, then WI is SCALE1 times the imaginary
 92 *          part of the eigenvalues.  WI will always be non-negative.
 93 *
 94 *  =====================================================================
 95 *
 96 *     .. Parameters ..
 97       DOUBLE PRECISION   ZERO, ONE, TWO
 98       PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0, TWO = 2.0D+0 )
 99       DOUBLE PRECISION   HALF
100       PARAMETER          ( HALF = ONE / TWO )
101       DOUBLE PRECISION   FUZZY1
102       PARAMETER          ( FUZZY1 = ONE+1.0D-5 )
103 *     ..
104 *     .. Local Scalars ..
105       DOUBLE PRECISION   A11, A12, A21, A22, ABI22, ANORM, AS11, AS12,
106      $                   AS22, ASCALE, B11, B12, B22, BINV11, BINV22,
107      $                   BMIN, BNORM, BSCALE, BSIZE, C1, C2, C3, C4, C5,
108      $                   DIFF, DISCR, PP, QQ, R, RTMAX, RTMIN, S1, S2,
109      $                   SAFMAX, SHIFT, SS, SUM, WABS, WBIG, WDET,
110      $                   WSCALE, WSIZE, WSMALL
111 *     ..
112 *     .. Intrinsic Functions ..
113       INTRINSIC          ABSMAXMINSIGNSQRT
114 *     ..
115 *     .. Executable Statements ..
116 *
117       RTMIN = SQRT( SAFMIN )
118       RTMAX = ONE / RTMIN
119       SAFMAX = ONE / SAFMIN
120 *
121 *     Scale A
122 *
123       ANORM = MAXABS( A( 11 ) )+ABS( A( 21 ) ),
124      $        ABS( A( 12 ) )+ABS( A( 22 ) ), SAFMIN )
125       ASCALE = ONE / ANORM
126       A11 = ASCALE*A( 11 )
127       A21 = ASCALE*A( 21 )
128       A12 = ASCALE*A( 12 )
129       A22 = ASCALE*A( 22 )
130 *
131 *     Perturb B if necessary to insure non-singularity
132 *
133       B11 = B( 11 )
134       B12 = B( 12 )
135       B22 = B( 22 )
136       BMIN = RTMIN*MAXABS( B11 ), ABS( B12 ), ABS( B22 ), RTMIN )
137       IFABS( B11 ).LT.BMIN )
138      $   B11 = SIGN( BMIN, B11 )
139       IFABS( B22 ).LT.BMIN )
140      $   B22 = SIGN( BMIN, B22 )
141 *
142 *     Scale B
143 *
144       BNORM = MAXABS( B11 ), ABS( B12 )+ABS( B22 ), SAFMIN )
145       BSIZE = MAXABS( B11 ), ABS( B22 ) )
146       BSCALE = ONE / BSIZE
147       B11 = B11*BSCALE
148       B12 = B12*BSCALE
149       B22 = B22*BSCALE
150 *
151 *     Compute larger eigenvalue by method described by C. van Loan
152 *
153 *     ( AS is A shifted by -SHIFT*B )
154 *
155       BINV11 = ONE / B11
156       BINV22 = ONE / B22
157       S1 = A11*BINV11
158       S2 = A22*BINV22
159       IFABS( S1 ).LE.ABS( S2 ) ) THEN
160          AS12 = A12 - S1*B12
161          AS22 = A22 - S1*B22
162          SS = A21*( BINV11*BINV22 )
163          ABI22 = AS22*BINV22 - SS*B12
164          PP = HALF*ABI22
165          SHIFT = S1
166       ELSE
167          AS12 = A12 - S2*B12
168          AS11 = A11 - S2*B11
169          SS = A21*( BINV11*BINV22 )
170          ABI22 = -SS*B12
171          PP = HALF*( AS11*BINV11+ABI22 )
172          SHIFT = S2
173       END IF
174       QQ = SS*AS12
175       IFABS( PP*RTMIN ).GE.ONE ) THEN
176          DISCR = ( RTMIN*PP )**2 + QQ*SAFMIN
177          R = SQRTABS( DISCR ) )*RTMAX
178       ELSE
179          IF( PP**2+ABS( QQ ).LE.SAFMIN ) THEN
180             DISCR = ( RTMAX*PP )**2 + QQ*SAFMAX
181             R = SQRTABS( DISCR ) )*RTMIN
182          ELSE
183             DISCR = PP**2 + QQ
184             R = SQRTABS( DISCR ) )
185          END IF
186       END IF
187 *
188 *     Note: the test of R in the following IF is to cover the case when
189 *           DISCR is small and negative and is flushed to zero during
190 *           the calculation of R.  On machines which have a consistent
191 *           flush-to-zero threshhold and handle numbers above that
192 *           threshhold correctly, it would not be necessary.
193 *
194       IF( DISCR.GE.ZERO .OR. R.EQ.ZERO ) THEN
195          SUM = PP + SIGN( R, PP )
196          DIFF = PP - SIGN( R, PP )
197          WBIG = SHIFT + SUM
198 *
199 *        Compute smaller eigenvalue
200 *
201          WSMALL = SHIFT + DIFF
202          IF( HALF*ABS( WBIG ).GT.MAXABS( WSMALL ), SAFMIN ) ) THEN
203             WDET = ( A11*A22-A12*A21 )*( BINV11*BINV22 )
204             WSMALL = WDET / WBIG
205          END IF
206 *
207 *        Choose (real) eigenvalue closest to 2,2 element of A*B**(-1)
208 *        for WR1.
209 *
210          IF( PP.GT.ABI22 ) THEN
211             WR1 = MIN( WBIG, WSMALL )
212             WR2 = MAX( WBIG, WSMALL )
213          ELSE
214             WR1 = MAX( WBIG, WSMALL )
215             WR2 = MIN( WBIG, WSMALL )
216          END IF
217          WI = ZERO
218       ELSE
219 *
220 *        Complex eigenvalues
221 *
222          WR1 = SHIFT + PP
223          WR2 = WR1
224          WI = R
225       END IF
226 *
227 *     Further scaling to avoid underflow and overflow in computing
228 *     SCALE1 and overflow in computing w*B.
229 *
230 *     This scale factor (WSCALE) is bounded from above using C1 and C2,
231 *     and from below using C3 and C4.
232 *        C1 implements the condition  s A  must never overflow.
233 *        C2 implements the condition  w B  must never overflow.
234 *        C3, with C2,
235 *           implement the condition that s A - w B must never overflow.
236 *        C4 implements the condition  s    should not underflow.
237 *        C5 implements the condition  max(s,|w|) should be at least 2.
238 *
239       C1 = BSIZE*( SAFMIN*MAX( ONE, ASCALE ) )
240       C2 = SAFMIN*MAX( ONE, BNORM )
241       C3 = BSIZE*SAFMIN
242       IF( ASCALE.LE.ONE .AND. BSIZE.LE.ONE ) THEN
243          C4 = MIN( ONE, ( ASCALE / SAFMIN )*BSIZE )
244       ELSE
245          C4 = ONE
246       END IF
247       IF( ASCALE.LE.ONE .OR. BSIZE.LE.ONE ) THEN
248          C5 = MIN( ONE, ASCALE*BSIZE )
249       ELSE
250          C5 = ONE
251       END IF
252 *
253 *     Scale first eigenvalue
254 *
255       WABS = ABS( WR1 ) + ABS( WI )
256       WSIZE = MAX( SAFMIN, C1, FUZZY1*( WABS*C2+C3 ),
257      $        MIN( C4, HALF*MAX( WABS, C5 ) ) )
258       IF( WSIZE.NE.ONE ) THEN
259          WSCALE = ONE / WSIZE
260          IF( WSIZE.GT.ONE ) THEN
261             SCALE1 = ( MAX( ASCALE, BSIZE )*WSCALE )*
262      $               MIN( ASCALE, BSIZE )
263          ELSE
264             SCALE1 = ( MIN( ASCALE, BSIZE )*WSCALE )*
265      $               MAX( ASCALE, BSIZE )
266          END IF
267          WR1 = WR1*WSCALE
268          IF( WI.NE.ZERO ) THEN
269             WI = WI*WSCALE
270             WR2 = WR1
271             SCALE2 = SCALE1
272          END IF
273       ELSE
274          SCALE1 = ASCALE*BSIZE
275          SCALE2 = SCALE1
276       END IF
277 *
278 *     Scale second eigenvalue (if real)
279 *
280       IF( WI.EQ.ZERO ) THEN
281          WSIZE = MAX( SAFMIN, C1, FUZZY1*ABS( WR2 )*C2+C3 ),
282      $           MIN( C4, HALF*MAXABS( WR2 ), C5 ) ) )
283          IF( WSIZE.NE.ONE ) THEN
284             WSCALE = ONE / WSIZE
285             IF( WSIZE.GT.ONE ) THEN
286                SCALE2 = ( MAX( ASCALE, BSIZE )*WSCALE )*
287      $                  MIN( ASCALE, BSIZE )
288             ELSE
289                SCALE2 = ( MIN( ASCALE, BSIZE )*WSCALE )*
290      $                  MAX( ASCALE, BSIZE )
291             END IF
292             WR2 = WR2*WSCALE
293          ELSE
294             SCALE2 = ASCALE*BSIZE
295          END IF
296       END IF
297 *
298 *     End of DLAG2
299 *
300       RETURN
301       END