LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dlanv2.f
Go to the documentation of this file.
1*> \brief \b DLANV2 computes the Schur factorization of a real 2-by-2 nonsymmetric matrix in standard form.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DLANV2 + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlanv2.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlanv2.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlanv2.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DLANV2( A, B, C, D, RT1R, RT1I, RT2R, RT2I, CS, SN )
20*
21* .. Scalar Arguments ..
22* DOUBLE PRECISION A, B, C, CS, D, RT1I, RT1R, RT2I, RT2R, SN
23* ..
24*
25*
26*> \par Purpose:
27* =============
28*>
29*> \verbatim
30*>
31*> DLANV2 computes the Schur factorization of a real 2-by-2 nonsymmetric
32*> matrix in standard form:
33*>
34*> [ A B ] = [ CS -SN ] [ AA BB ] [ CS SN ]
35*> [ C D ] [ SN CS ] [ CC DD ] [-SN CS ]
36*>
37*> where either
38*> 1) CC = 0 so that AA and DD are real eigenvalues of the matrix, or
39*> 2) AA = DD and BB*CC < 0, so that AA + or - sqrt(BB*CC) are complex
40*> conjugate eigenvalues.
41*> \endverbatim
42*
43* Arguments:
44* ==========
45*
46*> \param[in,out] A
47*> \verbatim
48*> A is DOUBLE PRECISION
49*> \endverbatim
50*>
51*> \param[in,out] B
52*> \verbatim
53*> B is DOUBLE PRECISION
54*> \endverbatim
55*>
56*> \param[in,out] C
57*> \verbatim
58*> C is DOUBLE PRECISION
59*> \endverbatim
60*>
61*> \param[in,out] D
62*> \verbatim
63*> D is DOUBLE PRECISION
64*> On entry, the elements of the input matrix.
65*> On exit, they are overwritten by the elements of the
66*> standardised Schur form.
67*> \endverbatim
68*>
69*> \param[out] RT1R
70*> \verbatim
71*> RT1R is DOUBLE PRECISION
72*> \endverbatim
73*>
74*> \param[out] RT1I
75*> \verbatim
76*> RT1I is DOUBLE PRECISION
77*> \endverbatim
78*>
79*> \param[out] RT2R
80*> \verbatim
81*> RT2R is DOUBLE PRECISION
82*> \endverbatim
83*>
84*> \param[out] RT2I
85*> \verbatim
86*> RT2I is DOUBLE PRECISION
87*> The real and imaginary parts of the eigenvalues. If the
88*> eigenvalues are a complex conjugate pair, RT1I > 0.
89*> \endverbatim
90*>
91*> \param[out] CS
92*> \verbatim
93*> CS is DOUBLE PRECISION
94*> \endverbatim
95*>
96*> \param[out] SN
97*> \verbatim
98*> SN is DOUBLE PRECISION
99*> Parameters of the rotation matrix.
100*> \endverbatim
101*
102* Authors:
103* ========
104*
105*> \author Univ. of Tennessee
106*> \author Univ. of California Berkeley
107*> \author Univ. of Colorado Denver
108*> \author NAG Ltd.
109*
110*> \ingroup lanv2
111*
112*> \par Further Details:
113* =====================
114*>
115*> \verbatim
116*>
117*> Modified by V. Sima, Research Institute for Informatics, Bucharest,
118*> Romania, to reduce the risk of cancellation errors,
119*> when computing real eigenvalues, and to ensure, if possible, that
120*> abs(RT1R) >= abs(RT2R).
121*> \endverbatim
122*>
123* =====================================================================
124 SUBROUTINE dlanv2( A, B, C, D, RT1R, RT1I, RT2R, RT2I, CS, SN )
125*
126* -- LAPACK auxiliary routine --
127* -- LAPACK is a software package provided by Univ. of Tennessee, --
128* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
129*
130* .. Scalar Arguments ..
131 DOUBLE PRECISION A, B, C, CS, D, RT1I, RT1R, RT2I, RT2R, SN
132* ..
133*
134* =====================================================================
135*
136* .. Parameters ..
137 DOUBLE PRECISION ZERO, HALF, ONE, TWO
138 parameter( zero = 0.0d+0, half = 0.5d+0, one = 1.0d+0,
139 $ two = 2.0d0 )
140 DOUBLE PRECISION MULTPL
141 parameter( multpl = 4.0d+0 )
142* ..
143* .. Local Scalars ..
144 DOUBLE PRECISION AA, BB, BCMAX, BCMIS, CC, CS1, DD, EPS, P, SAB,
145 $ SAC, SCALE, SIGMA, SN1, TAU, TEMP, Z, SAFMIN,
146 $ SAFMN2, SAFMX2
147 INTEGER COUNT
148* ..
149* .. External Functions ..
150 DOUBLE PRECISION DLAMCH, DLAPY2
151 EXTERNAL dlamch, dlapy2
152* ..
153* .. Intrinsic Functions ..
154 INTRINSIC abs, max, min, sign, sqrt
155* ..
156* .. Executable Statements ..
157*
158 safmin = dlamch( 'S' )
159 eps = dlamch( 'P' )
160 safmn2 = dlamch( 'B' )**int( log( safmin / eps ) /
161 $ log( dlamch( 'B' ) ) / two )
162 safmx2 = one / safmn2
163 IF( c.EQ.zero ) THEN
164 cs = one
165 sn = zero
166*
167 ELSE IF( b.EQ.zero ) THEN
168*
169* Swap rows and columns
170*
171 cs = zero
172 sn = one
173 temp = d
174 d = a
175 a = temp
176 b = -c
177 c = zero
178*
179 ELSE IF( ( a-d ).EQ.zero .AND. sign( one, b ).NE.sign( one, c ) )
180 $ THEN
181 cs = one
182 sn = zero
183*
184 ELSE
185*
186 temp = a - d
187 p = half*temp
188 bcmax = max( abs( b ), abs( c ) )
189 bcmis = min( abs( b ), abs( c ) )*sign( one, b )*sign( one, c )
190 scale = max( abs( p ), bcmax )
191 z = ( p / scale )*p + ( bcmax / scale )*bcmis
192*
193* If Z is of the order of the machine accuracy, postpone the
194* decision on the nature of eigenvalues
195*
196 IF( z.GE.multpl*eps ) THEN
197*
198* Real eigenvalues. Compute A and D.
199*
200 z = p + sign( sqrt( scale )*sqrt( z ), p )
201 a = d + z
202 d = d - ( bcmax / z )*bcmis
203*
204* Compute B and the rotation matrix
205*
206 tau = dlapy2( c, z )
207 cs = z / tau
208 sn = c / tau
209 b = b - c
210 c = zero
211*
212 ELSE
213*
214* Complex eigenvalues, or real (almost) equal eigenvalues.
215* Make diagonal elements equal.
216*
217 count = 0
218 sigma = b + c
219 10 CONTINUE
220 count = count + 1
221 scale = max( abs(temp), abs(sigma) )
222 IF( scale.GE.safmx2 ) THEN
223 sigma = sigma * safmn2
224 temp = temp * safmn2
225 IF (count .LE. 20)
226 $ GOTO 10
227 END IF
228 IF( scale.LE.safmn2 ) THEN
229 sigma = sigma * safmx2
230 temp = temp * safmx2
231 IF (count .LE. 20)
232 $ GOTO 10
233 END IF
234 p = half*temp
235 tau = dlapy2( sigma, temp )
236 cs = sqrt( half*( one+abs( sigma ) / tau ) )
237 sn = -( p / ( tau*cs ) )*sign( one, sigma )
238*
239* Compute [ AA BB ] = [ A B ] [ CS -SN ]
240* [ CC DD ] [ C D ] [ SN CS ]
241*
242 aa = a*cs + b*sn
243 bb = -a*sn + b*cs
244 cc = c*cs + d*sn
245 dd = -c*sn + d*cs
246*
247* Compute [ A B ] = [ CS SN ] [ AA BB ]
248* [ C D ] [-SN CS ] [ CC DD ]
249*
250* Note: Some of the multiplications are wrapped in parentheses to
251* prevent compilers from using FMA instructions. See
252* https://github.com/Reference-LAPACK/lapack/issues/1031.
253*
254 a = aa*cs + cc*sn
255 b = ( bb*cs ) + ( dd*sn )
256 c = -( aa*sn ) + ( cc*cs )
257 d = -bb*sn + dd*cs
258*
259 temp = half*( a+d )
260 a = temp
261 d = temp
262*
263 IF( c.NE.zero ) THEN
264 IF( b.NE.zero ) THEN
265 IF( sign( one, b ).EQ.sign( one, c ) ) THEN
266*
267* Real eigenvalues: reduce to upper triangular form
268*
269 sab = sqrt( abs( b ) )
270 sac = sqrt( abs( c ) )
271 p = sign( sab*sac, c )
272 tau = one / sqrt( abs( b+c ) )
273 a = temp + p
274 d = temp - p
275 b = b - c
276 c = zero
277 cs1 = sab*tau
278 sn1 = sac*tau
279 temp = cs*cs1 - sn*sn1
280 sn = cs*sn1 + sn*cs1
281 cs = temp
282 END IF
283 ELSE
284 b = -c
285 c = zero
286 temp = cs
287 cs = -sn
288 sn = temp
289 END IF
290 END IF
291 END IF
292*
293 END IF
294*
295* Store eigenvalues in (RT1R,RT1I) and (RT2R,RT2I).
296*
297 rt1r = a
298 rt2r = d
299 IF( c.EQ.zero ) THEN
300 rt1i = zero
301 rt2i = zero
302 ELSE
303 rt1i = sqrt( abs( b ) )*sqrt( abs( c ) )
304 rt2i = -rt1i
305 END IF
306 RETURN
307*
308* End of DLANV2
309*
310 END
subroutine dlanv2(a, b, c, d, rt1r, rt1i, rt2r, rt2i, cs, sn)
DLANV2 computes the Schur factorization of a real 2-by-2 nonsymmetric matrix in standard form.
Definition dlanv2.f:125