LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ slag2()

subroutine slag2 ( real, dimension( lda, * ) a,
integer lda,
real, dimension( ldb, * ) b,
integer ldb,
real safmin,
real scale1,
real scale2,
real wr1,
real wr2,
real wi )

SLAG2 computes the eigenvalues of a 2-by-2 generalized eigenvalue problem, with scaling as necessary to avoid over-/underflow.

Download SLAG2 + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> SLAG2 computes the eigenvalues of a 2 x 2 generalized eigenvalue
!> problem  A - w B, with scaling as necessary to avoid over-/underflow.
!>
!> The scaling factor  results in a modified eigenvalue equation
!>
!>     s A - w B
!>
!> where  s  is a non-negative scaling factor chosen so that  w,  w B,
!> and  s A  do not overflow and, if possible, do not underflow, either.
!> 
Parameters
[in]A
!>          A is REAL array, dimension (LDA, 2)
!>          On entry, the 2 x 2 matrix A.  It is assumed that its 1-norm
!>          is less than 1/SAFMIN.  Entries less than
!>          sqrt(SAFMIN)*norm(A) are subject to being treated as zero.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the array A.  LDA >= 2.
!> 
[in]B
!>          B is REAL array, dimension (LDB, 2)
!>          On entry, the 2 x 2 upper triangular matrix B.  It is
!>          assumed that the one-norm of B is less than 1/SAFMIN.  The
!>          diagonals should be at least sqrt(SAFMIN) times the largest
!>          element of B (in absolute value); if a diagonal is smaller
!>          than that, then  +/- sqrt(SAFMIN) will be used instead of
!>          that diagonal.
!> 
[in]LDB
!>          LDB is INTEGER
!>          The leading dimension of the array B.  LDB >= 2.
!> 
[in]SAFMIN
!>          SAFMIN is REAL
!>          The smallest positive number s.t. 1/SAFMIN does not
!>          overflow.  (This should always be SLAMCH('S') -- it is an
!>          argument in order to avoid having to call SLAMCH frequently.)
!> 
[out]SCALE1
!>          SCALE1 is REAL
!>          A scaling factor used to avoid over-/underflow in the
!>          eigenvalue equation which defines the first eigenvalue.  If
!>          the eigenvalues are complex, then the eigenvalues are
!>          ( WR1  +/-  WI i ) / SCALE1  (which may lie outside the
!>          exponent range of the machine), SCALE1=SCALE2, and SCALE1
!>          will always be positive.  If the eigenvalues are real, then
!>          the first (real) eigenvalue is  WR1 / SCALE1 , but this may
!>          overflow or underflow, and in fact, SCALE1 may be zero or
!>          less than the underflow threshold if the exact eigenvalue
!>          is sufficiently large.
!> 
[out]SCALE2
!>          SCALE2 is REAL
!>          A scaling factor used to avoid over-/underflow in the
!>          eigenvalue equation which defines the second eigenvalue.  If
!>          the eigenvalues are complex, then SCALE2=SCALE1.  If the
!>          eigenvalues are real, then the second (real) eigenvalue is
!>          WR2 / SCALE2 , but this may overflow or underflow, and in
!>          fact, SCALE2 may be zero or less than the underflow
!>          threshold if the exact eigenvalue is sufficiently large.
!> 
[out]WR1
!>          WR1 is REAL
!>          If the eigenvalue is real, then WR1 is SCALE1 times the
!>          eigenvalue closest to the (2,2) element of A B**(-1).  If the
!>          eigenvalue is complex, then WR1=WR2 is SCALE1 times the real
!>          part of the eigenvalues.
!> 
[out]WR2
!>          WR2 is REAL
!>          If the eigenvalue is real, then WR2 is SCALE2 times the
!>          other eigenvalue.  If the eigenvalue is complex, then
!>          WR1=WR2 is SCALE1 times the real part of the eigenvalues.
!> 
[out]WI
!>          WI is REAL
!>          If the eigenvalue is real, then WI is zero.  If the
!>          eigenvalue is complex, then WI is SCALE1 times the imaginary
!>          part of the eigenvalues.  WI will always be non-negative.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 152 of file slag2.f.

154*
155* -- LAPACK auxiliary routine --
156* -- LAPACK is a software package provided by Univ. of Tennessee, --
157* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
158*
159* .. Scalar Arguments ..
160 INTEGER LDA, LDB
161 REAL SAFMIN, SCALE1, SCALE2, WI, WR1, WR2
162* ..
163* .. Array Arguments ..
164 REAL A( LDA, * ), B( LDB, * )
165* ..
166*
167* =====================================================================
168*
169* .. Parameters ..
170 REAL ZERO, ONE, TWO
171 parameter( zero = 0.0e+0, one = 1.0e+0, two = 2.0e+0 )
172 REAL HALF
173 parameter( half = one / two )
174 REAL FUZZY1
175 parameter( fuzzy1 = one+1.0e-5 )
176* ..
177* .. Local Scalars ..
178 REAL A11, A12, A21, A22, ABI22, ANORM, AS11, AS12,
179 $ AS22, ASCALE, B11, B12, B22, BINV11, BINV22,
180 $ BMIN, BNORM, BSCALE, BSIZE, C1, C2, C3, C4, C5,
181 $ DIFF, DISCR, PP, QQ, R, RTMAX, RTMIN, S1, S2,
182 $ SAFMAX, SHIFT, SS, SUM, WABS, WBIG, WDET,
183 $ WSCALE, WSIZE, WSMALL
184* ..
185* .. Intrinsic Functions ..
186 INTRINSIC abs, max, min, sign, sqrt
187* ..
188* .. Executable Statements ..
189*
190 rtmin = sqrt( safmin )
191 rtmax = one / rtmin
192 safmax = one / safmin
193*
194* Scale A
195*
196 anorm = max( abs( a( 1, 1 ) )+abs( a( 2, 1 ) ),
197 $ abs( a( 1, 2 ) )+abs( a( 2, 2 ) ), safmin )
198 ascale = one / anorm
199 a11 = ascale*a( 1, 1 )
200 a21 = ascale*a( 2, 1 )
201 a12 = ascale*a( 1, 2 )
202 a22 = ascale*a( 2, 2 )
203*
204* Perturb B if necessary to insure non-singularity
205*
206 b11 = b( 1, 1 )
207 b12 = b( 1, 2 )
208 b22 = b( 2, 2 )
209 bmin = rtmin*max( abs( b11 ), abs( b12 ), abs( b22 ), rtmin )
210 IF( abs( b11 ).LT.bmin )
211 $ b11 = sign( bmin, b11 )
212 IF( abs( b22 ).LT.bmin )
213 $ b22 = sign( bmin, b22 )
214*
215* Scale B
216*
217 bnorm = max( abs( b11 ), abs( b12 )+abs( b22 ), safmin )
218 bsize = max( abs( b11 ), abs( b22 ) )
219 bscale = one / bsize
220 b11 = b11*bscale
221 b12 = b12*bscale
222 b22 = b22*bscale
223*
224* Compute larger eigenvalue by method described by C. van Loan
225*
226* ( AS is A shifted by -SHIFT*B )
227*
228 binv11 = one / b11
229 binv22 = one / b22
230 s1 = a11*binv11
231 s2 = a22*binv22
232 IF( abs( s1 ).LE.abs( s2 ) ) THEN
233 as12 = a12 - s1*b12
234 as22 = a22 - s1*b22
235 ss = a21*( binv11*binv22 )
236 abi22 = as22*binv22 - ss*b12
237 pp = half*abi22
238 shift = s1
239 ELSE
240 as12 = a12 - s2*b12
241 as11 = a11 - s2*b11
242 ss = a21*( binv11*binv22 )
243 abi22 = -ss*b12
244 pp = half*( as11*binv11+abi22 )
245 shift = s2
246 END IF
247 qq = ss*as12
248 IF( abs( pp*rtmin ).GE.one ) THEN
249 discr = ( rtmin*pp )**2 + qq*safmin
250 r = sqrt( abs( discr ) )*rtmax
251 ELSE
252 IF( pp**2+abs( qq ).LE.safmin ) THEN
253 discr = ( rtmax*pp )**2 + qq*safmax
254 r = sqrt( abs( discr ) )*rtmin
255 ELSE
256 discr = pp**2 + qq
257 r = sqrt( abs( discr ) )
258 END IF
259 END IF
260*
261* Note: the test of R in the following IF is to cover the case when
262* DISCR is small and negative and is flushed to zero during
263* the calculation of R. On machines which have a consistent
264* flush-to-zero threshold and handle numbers above that
265* threshold correctly, it would not be necessary.
266*
267 IF( discr.GE.zero .OR. r.EQ.zero ) THEN
268 sum = pp + sign( r, pp )
269 diff = pp - sign( r, pp )
270 wbig = shift + sum
271*
272* Compute smaller eigenvalue
273*
274 wsmall = shift + diff
275 IF( half*abs( wbig ).GT.max( abs( wsmall ), safmin ) ) THEN
276 wdet = ( a11*a22-a12*a21 )*( binv11*binv22 )
277 wsmall = wdet / wbig
278 END IF
279*
280* Choose (real) eigenvalue closest to 2,2 element of A*B**(-1)
281* for WR1.
282*
283 IF( pp.GT.abi22 ) THEN
284 wr1 = min( wbig, wsmall )
285 wr2 = max( wbig, wsmall )
286 ELSE
287 wr1 = max( wbig, wsmall )
288 wr2 = min( wbig, wsmall )
289 END IF
290 wi = zero
291 ELSE
292*
293* Complex eigenvalues
294*
295 wr1 = shift + pp
296 wr2 = wr1
297 wi = r
298 END IF
299*
300* Further scaling to avoid underflow and overflow in computing
301* SCALE1 and overflow in computing w*B.
302*
303* This scale factor (WSCALE) is bounded from above using C1 and C2,
304* and from below using C3 and C4.
305* C1 implements the condition s A must never overflow.
306* C2 implements the condition w B must never overflow.
307* C3, with C2,
308* implement the condition that s A - w B must never overflow.
309* C4 implements the condition s should not underflow.
310* C5 implements the condition max(s,|w|) should be at least 2.
311*
312 c1 = bsize*( safmin*max( one, ascale ) )
313 c2 = safmin*max( one, bnorm )
314 c3 = bsize*safmin
315 IF( ascale.LE.one .AND. bsize.LE.one ) THEN
316 c4 = min( one, ( ascale / safmin )*bsize )
317 ELSE
318 c4 = one
319 END IF
320 IF( ascale.LE.one .OR. bsize.LE.one ) THEN
321 c5 = min( one, ascale*bsize )
322 ELSE
323 c5 = one
324 END IF
325*
326* Scale first eigenvalue
327*
328 wabs = abs( wr1 ) + abs( wi )
329 wsize = max( safmin, c1, fuzzy1*( wabs*c2+c3 ),
330 $ min( c4, half*max( wabs, c5 ) ) )
331 IF( wsize.NE.one ) THEN
332 wscale = one / wsize
333 IF( wsize.GT.one ) THEN
334 scale1 = ( max( ascale, bsize )*wscale )*
335 $ min( ascale, bsize )
336 ELSE
337 scale1 = ( min( ascale, bsize )*wscale )*
338 $ max( ascale, bsize )
339 END IF
340 wr1 = wr1*wscale
341 IF( wi.NE.zero ) THEN
342 wi = wi*wscale
343 wr2 = wr1
344 scale2 = scale1
345 END IF
346 ELSE
347 scale1 = ascale*bsize
348 scale2 = scale1
349 END IF
350*
351* Scale second eigenvalue (if real)
352*
353 IF( wi.EQ.zero ) THEN
354 wsize = max( safmin, c1, fuzzy1*( abs( wr2 )*c2+c3 ),
355 $ min( c4, half*max( abs( wr2 ), c5 ) ) )
356 IF( wsize.NE.one ) THEN
357 wscale = one / wsize
358 IF( wsize.GT.one ) THEN
359 scale2 = ( max( ascale, bsize )*wscale )*
360 $ min( ascale, bsize )
361 ELSE
362 scale2 = ( min( ascale, bsize )*wscale )*
363 $ max( ascale, bsize )
364 END IF
365 wr2 = wr2*wscale
366 ELSE
367 scale2 = ascale*bsize
368 END IF
369 END IF
370*
371* End of SLAG2
372*
373 RETURN
Here is the caller graph for this function: