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