LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dlas2.f
Go to the documentation of this file.
1*> \brief \b DLAS2 computes singular values of a 2-by-2 triangular matrix.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DLAS2 + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlas2.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlas2.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlas2.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DLAS2( F, G, H, SSMIN, SSMAX )
20*
21* .. Scalar Arguments ..
22* DOUBLE PRECISION F, G, H, SSMAX, SSMIN
23* ..
24*
25*
26*> \par Purpose:
27* =============
28*>
29*> \verbatim
30*>
31*> DLAS2 computes the singular values of the 2-by-2 matrix
32*> [ F G ]
33*> [ 0 H ].
34*> On return, SSMIN is the smaller singular value and SSMAX is the
35*> larger singular value.
36*> \endverbatim
37*
38* Arguments:
39* ==========
40*
41*> \param[in] F
42*> \verbatim
43*> F is DOUBLE PRECISION
44*> The (1,1) element of the 2-by-2 matrix.
45*> \endverbatim
46*>
47*> \param[in] G
48*> \verbatim
49*> G is DOUBLE PRECISION
50*> The (1,2) element of the 2-by-2 matrix.
51*> \endverbatim
52*>
53*> \param[in] H
54*> \verbatim
55*> H is DOUBLE PRECISION
56*> The (2,2) element of the 2-by-2 matrix.
57*> \endverbatim
58*>
59*> \param[out] SSMIN
60*> \verbatim
61*> SSMIN is DOUBLE PRECISION
62*> The smaller singular value.
63*> \endverbatim
64*>
65*> \param[out] SSMAX
66*> \verbatim
67*> SSMAX is DOUBLE PRECISION
68*> The larger singular value.
69*> \endverbatim
70*
71* Authors:
72* ========
73*
74*> \author Univ. of Tennessee
75*> \author Univ. of California Berkeley
76*> \author Univ. of Colorado Denver
77*> \author NAG Ltd.
78*
79*> \ingroup las2
80*
81*> \par Further Details:
82* =====================
83*>
84*> \verbatim
85*>
86*> Barring over/underflow, all output quantities are correct to within
87*> a few units in the last place (ulps), even in the absence of a guard
88*> digit in addition/subtraction.
89*>
90*> In IEEE arithmetic, the code works correctly if one matrix element is
91*> infinite.
92*>
93*> Overflow will not occur unless the largest singular value itself
94*> overflows, or is within a few ulps of overflow.
95*>
96*> Underflow is harmless if underflow is gradual. Otherwise, results
97*> may correspond to a matrix modified by perturbations of size near
98*> the underflow threshold.
99*> \endverbatim
100*>
101* =====================================================================
102 SUBROUTINE dlas2( F, G, H, SSMIN, SSMAX )
103*
104* -- LAPACK auxiliary routine --
105* -- LAPACK is a software package provided by Univ. of Tennessee, --
106* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
107*
108* .. Scalar Arguments ..
109 DOUBLE PRECISION F, G, H, SSMAX, SSMIN
110* ..
111*
112* ====================================================================
113*
114* .. Parameters ..
115 DOUBLE PRECISION ZERO
116 parameter( zero = 0.0d0 )
117 DOUBLE PRECISION ONE
118 parameter( one = 1.0d0 )
119 DOUBLE PRECISION TWO
120 parameter( two = 2.0d0 )
121* ..
122* .. Local Scalars ..
123 DOUBLE PRECISION AS, AT, AU, C, FA, FHMN, FHMX, GA, HA
124* ..
125* .. Intrinsic Functions ..
126 INTRINSIC abs, max, min, sqrt
127* ..
128* .. Executable Statements ..
129*
130 fa = abs( f )
131 ga = abs( g )
132 ha = abs( h )
133 fhmn = min( fa, ha )
134 fhmx = max( fa, ha )
135 IF( fhmn.EQ.zero ) THEN
136 ssmin = zero
137 IF( fhmx.EQ.zero ) THEN
138 ssmax = ga
139 ELSE
140 ssmax = max( fhmx, ga )*sqrt( one+
141 $ ( min( fhmx, ga ) / max( fhmx, ga ) )**2 )
142 END IF
143 ELSE
144 IF( ga.LT.fhmx ) THEN
145 as = one + fhmn / fhmx
146 at = ( fhmx-fhmn ) / fhmx
147 au = ( ga / fhmx )**2
148 c = two / ( sqrt( as*as+au )+sqrt( at*at+au ) )
149 ssmin = fhmn*c
150 ssmax = fhmx / c
151 ELSE
152 au = fhmx / ga
153 IF( au.EQ.zero ) THEN
154*
155* Avoid possible harmful underflow if exponent range
156* asymmetric (true SSMIN may not underflow even if
157* AU underflows)
158*
159 ssmin = ( fhmn*fhmx ) / ga
160 ssmax = ga
161 ELSE
162 as = one + fhmn / fhmx
163 at = ( fhmx-fhmn ) / fhmx
164 c = one / ( sqrt( one+( as*au )**2 )+
165 $ sqrt( one+( at*au )**2 ) )
166 ssmin = ( fhmn*c )*au
167 ssmin = ssmin + ssmin
168 ssmax = ga / ( c+c )
169 END IF
170 END IF
171 END IF
172 RETURN
173*
174* End of DLAS2
175*
176 END
subroutine dlas2(f, g, h, ssmin, ssmax)
DLAS2 computes singular values of a 2-by-2 triangular matrix.
Definition dlas2.f:103