001:       SUBROUTINE SLAS2( F, G, H, SSMIN, SSMAX )
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:       REAL               F, G, H, SSMAX, SSMIN
010: *     ..
011: *
012: *  Purpose
013: *  =======
014: *
015: *  SLAS2  computes the singular values of the 2-by-2 matrix
016: *     [  F   G  ]
017: *     [  0   H  ].
018: *  On return, SSMIN is the smaller singular value and SSMAX is the
019: *  larger singular value.
020: *
021: *  Arguments
022: *  =========
023: *
024: *  F       (input) REAL
025: *          The (1,1) element of the 2-by-2 matrix.
026: *
027: *  G       (input) REAL
028: *          The (1,2) element of the 2-by-2 matrix.
029: *
030: *  H       (input) REAL
031: *          The (2,2) element of the 2-by-2 matrix.
032: *
033: *  SSMIN   (output) REAL
034: *          The smaller singular value.
035: *
036: *  SSMAX   (output) REAL
037: *          The larger singular value.
038: *
039: *  Further Details
040: *  ===============
041: *
042: *  Barring over/underflow, all output quantities are correct to within
043: *  a few units in the last place (ulps), even in the absence of a guard
044: *  digit in addition/subtraction.
045: *
046: *  In IEEE arithmetic, the code works correctly if one matrix element is
047: *  infinite.
048: *
049: *  Overflow will not occur unless the largest singular value itself
050: *  overflows, or is within a few ulps of overflow. (On machines with
051: *  partial overflow, like the Cray, overflow may occur if the largest
052: *  singular value is within a factor of 2 of overflow.)
053: *
054: *  Underflow is harmless if underflow is gradual. Otherwise, results
055: *  may correspond to a matrix modified by perturbations of size near
056: *  the underflow threshold.
057: *
058: *  ====================================================================
059: *
060: *     .. Parameters ..
061:       REAL               ZERO
062:       PARAMETER          ( ZERO = 0.0E0 )
063:       REAL               ONE
064:       PARAMETER          ( ONE = 1.0E0 )
065:       REAL               TWO
066:       PARAMETER          ( TWO = 2.0E0 )
067: *     ..
068: *     .. Local Scalars ..
069:       REAL               AS, AT, AU, C, FA, FHMN, FHMX, GA, HA
070: *     ..
071: *     .. Intrinsic Functions ..
072:       INTRINSIC          ABS, MAX, MIN, SQRT
073: *     ..
074: *     .. Executable Statements ..
075: *
076:       FA = ABS( F )
077:       GA = ABS( G )
078:       HA = ABS( H )
079:       FHMN = MIN( FA, HA )
080:       FHMX = MAX( FA, HA )
081:       IF( FHMN.EQ.ZERO ) THEN
082:          SSMIN = ZERO
083:          IF( FHMX.EQ.ZERO ) THEN
084:             SSMAX = GA
085:          ELSE
086:             SSMAX = MAX( FHMX, GA )*SQRT( ONE+
087:      $              ( MIN( FHMX, GA ) / MAX( FHMX, GA ) )**2 )
088:          END IF
089:       ELSE
090:          IF( GA.LT.FHMX ) THEN
091:             AS = ONE + FHMN / FHMX
092:             AT = ( FHMX-FHMN ) / FHMX
093:             AU = ( GA / FHMX )**2
094:             C = TWO / ( SQRT( AS*AS+AU )+SQRT( AT*AT+AU ) )
095:             SSMIN = FHMN*C
096:             SSMAX = FHMX / C
097:          ELSE
098:             AU = FHMX / GA
099:             IF( AU.EQ.ZERO ) THEN
100: *
101: *              Avoid possible harmful underflow if exponent range
102: *              asymmetric (true SSMIN may not underflow even if
103: *              AU underflows)
104: *
105:                SSMIN = ( FHMN*FHMX ) / GA
106:                SSMAX = GA
107:             ELSE
108:                AS = ONE + FHMN / FHMX
109:                AT = ( FHMX-FHMN ) / FHMX
110:                C = ONE / ( SQRT( ONE+( AS*AU )**2 )+
111:      $             SQRT( ONE+( AT*AU )**2 ) )
112:                SSMIN = ( FHMN*C )*AU
113:                SSMIN = SSMIN + SSMIN
114:                SSMAX = GA / ( C+C )
115:             END IF
116:          END IF
117:       END IF
118:       RETURN
119: *
120: *     End of SLAS2
121: *
122:       END
123: