LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
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 *> \htmlonly
9 *> Download DLANV2 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlanv2.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlanv2.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlanv2.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE DLANV2( A, B, C, D, RT1R, RT1I, RT2R, RT2I, CS, SN )
22 *
23 * .. Scalar Arguments ..
24 * DOUBLE PRECISION A, B, C, CS, D, RT1I, RT1R, RT2I, RT2R, SN
25 * ..
26 *
27 *
28 *> \par Purpose:
29 * =============
30 *>
31 *> \verbatim
32 *>
33 *> DLANV2 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 DOUBLE PRECISION
51 *> \endverbatim
52 *>
53 *> \param[in,out] B
54 *> \verbatim
55 *> B is DOUBLE PRECISION
56 *> \endverbatim
57 *>
58 *> \param[in,out] C
59 *> \verbatim
60 *> C is DOUBLE PRECISION
61 *> \endverbatim
62 *>
63 *> \param[in,out] D
64 *> \verbatim
65 *> D is DOUBLE PRECISION
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 DOUBLE PRECISION
74 *> \endverbatim
75 *>
76 *> \param[out] RT1I
77 *> \verbatim
78 *> RT1I is DOUBLE PRECISION
79 *> \endverbatim
80 *>
81 *> \param[out] RT2R
82 *> \verbatim
83 *> RT2R is DOUBLE PRECISION
84 *> \endverbatim
85 *>
86 *> \param[out] RT2I
87 *> \verbatim
88 *> RT2I is DOUBLE PRECISION
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 DOUBLE PRECISION
96 *> \endverbatim
97 *>
98 *> \param[out] SN
99 *> \verbatim
100 *> SN is DOUBLE PRECISION
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 *> \date September 2012
113 *
114 *> \ingroup doubleOTHERauxiliary
115 *
116 *> \par Further Details:
117 * =====================
118 *>
119 *> \verbatim
120 *>
121 *> Modified by V. Sima, Research Institute for Informatics, Bucharest,
122 *> Romania, to reduce the risk of cancellation errors,
123 *> when computing real eigenvalues, and to ensure, if possible, that
124 *> abs(RT1R) >= abs(RT2R).
125 *> \endverbatim
126 *>
127 * =====================================================================
128  SUBROUTINE dlanv2( A, B, C, D, RT1R, RT1I, RT2R, RT2I, CS, SN )
129 *
130 * -- LAPACK auxiliary routine (version 3.4.2) --
131 * -- LAPACK is a software package provided by Univ. of Tennessee, --
132 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
133 * September 2012
134 *
135 * .. Scalar Arguments ..
136  DOUBLE PRECISION a, b, c, cs, d, rt1i, rt1r, rt2i, rt2r, sn
137 * ..
138 *
139 * =====================================================================
140 *
141 * .. Parameters ..
142  DOUBLE PRECISION zero, half, one
143  parameter( zero = 0.0d+0, half = 0.5d+0, one = 1.0d+0 )
144  DOUBLE PRECISION multpl
145  parameter( multpl = 4.0d+0 )
146 * ..
147 * .. Local Scalars ..
148  DOUBLE PRECISION aa, bb, bcmax, bcmis, cc, cs1, dd, eps, p, sab,
149  $ sac, scale, sigma, sn1, tau, temp, z
150 * ..
151 * .. External Functions ..
152  DOUBLE PRECISION dlamch, dlapy2
153  EXTERNAL dlamch, dlapy2
154 * ..
155 * .. Intrinsic Functions ..
156  INTRINSIC abs, max, min, sign, sqrt
157 * ..
158 * .. Executable Statements ..
159 *
160  eps = dlamch( 'P' )
161  IF( c.EQ.zero ) THEN
162  cs = one
163  sn = zero
164  go to 10
165 *
166  ELSE IF( b.EQ.zero ) THEN
167 *
168 * Swap rows and columns
169 *
170  cs = zero
171  sn = one
172  temp = d
173  d = a
174  a = temp
175  b = -c
176  c = zero
177  go to 10
178  ELSE IF( ( a-d ).EQ.zero .AND. sign( one, b ).NE.sign( one, c ) )
179  $ THEN
180  cs = one
181  sn = zero
182  go to 10
183  ELSE
184 *
185  temp = a - d
186  p = half*temp
187  bcmax = max( abs( b ), abs( c ) )
188  bcmis = min( abs( b ), abs( c ) )*sign( one, b )*sign( one, c )
189  scale = max( abs( p ), bcmax )
190  z = ( p / scale )*p + ( bcmax / scale )*bcmis
191 *
192 * If Z is of the order of the machine accuracy, postpone the
193 * decision on the nature of eigenvalues
194 *
195  IF( z.GE.multpl*eps ) THEN
196 *
197 * Real eigenvalues. Compute A and D.
198 *
199  z = p + sign( sqrt( scale )*sqrt( z ), p )
200  a = d + z
201  d = d - ( bcmax / z )*bcmis
202 *
203 * Compute B and the rotation matrix
204 *
205  tau = dlapy2( c, z )
206  cs = z / tau
207  sn = c / tau
208  b = b - c
209  c = zero
210  ELSE
211 *
212 * Complex eigenvalues, or real (almost) equal eigenvalues.
213 * Make diagonal elements equal.
214 *
215  sigma = b + c
216  tau = dlapy2( sigma, temp )
217  cs = sqrt( half*( one+abs( sigma ) / tau ) )
218  sn = -( p / ( tau*cs ) )*sign( one, sigma )
219 *
220 * Compute [ AA BB ] = [ A B ] [ CS -SN ]
221 * [ CC DD ] [ C D ] [ SN CS ]
222 *
223  aa = a*cs + b*sn
224  bb = -a*sn + b*cs
225  cc = c*cs + d*sn
226  dd = -c*sn + d*cs
227 *
228 * Compute [ A B ] = [ CS SN ] [ AA BB ]
229 * [ C D ] [-SN CS ] [ CC DD ]
230 *
231  a = aa*cs + cc*sn
232  b = bb*cs + dd*sn
233  c = -aa*sn + cc*cs
234  d = -bb*sn + dd*cs
235 *
236  temp = half*( a+d )
237  a = temp
238  d = temp
239 *
240  IF( c.NE.zero ) THEN
241  IF( b.NE.zero ) THEN
242  IF( sign( one, b ).EQ.sign( one, c ) ) THEN
243 *
244 * Real eigenvalues: reduce to upper triangular form
245 *
246  sab = sqrt( abs( b ) )
247  sac = sqrt( abs( c ) )
248  p = sign( sab*sac, c )
249  tau = one / sqrt( abs( b+c ) )
250  a = temp + p
251  d = temp - p
252  b = b - c
253  c = zero
254  cs1 = sab*tau
255  sn1 = sac*tau
256  temp = cs*cs1 - sn*sn1
257  sn = cs*sn1 + sn*cs1
258  cs = temp
259  END IF
260  ELSE
261  b = -c
262  c = zero
263  temp = cs
264  cs = -sn
265  sn = temp
266  END IF
267  END IF
268  END IF
269 *
270  END IF
271 *
272  10 continue
273 *
274 * Store eigenvalues in (RT1R,RT1I) and (RT2R,RT2I).
275 *
276  rt1r = a
277  rt2r = d
278  IF( c.EQ.zero ) THEN
279  rt1i = zero
280  rt2i = zero
281  ELSE
282  rt1i = sqrt( abs( b ) )*sqrt( abs( c ) )
283  rt2i = -rt1i
284  END IF
285  return
286 *
287 * End of DLANV2
288 *
289  END