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