LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dlanv2()

subroutine dlanv2 ( double precision  a,
double precision  b,
double precision  c,
double precision  d,
double precision  rt1r,
double precision  rt1i,
double precision  rt2r,
double precision  rt2i,
double precision  cs,
double precision  sn 
)

DLANV2 computes the Schur factorization of a real 2-by-2 nonsymmetric matrix in standard form.

Download DLANV2 + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 DLANV2 computes the Schur factorization of a real 2-by-2 nonsymmetric
 matrix in standard form:

      [ A  B ] = [ CS -SN ] [ AA  BB ] [ CS  SN ]
      [ C  D ]   [ SN  CS ] [ CC  DD ] [-SN  CS ]

 where either
 1) CC = 0 so that AA and DD are real eigenvalues of the matrix, or
 2) AA = DD and BB*CC < 0, so that AA + or - sqrt(BB*CC) are complex
 conjugate eigenvalues.
Parameters
[in,out]A
          A is DOUBLE PRECISION
[in,out]B
          B is DOUBLE PRECISION
[in,out]C
          C is DOUBLE PRECISION
[in,out]D
          D is DOUBLE PRECISION
          On entry, the elements of the input matrix.
          On exit, they are overwritten by the elements of the
          standardised Schur form.
[out]RT1R
          RT1R is DOUBLE PRECISION
[out]RT1I
          RT1I is DOUBLE PRECISION
[out]RT2R
          RT2R is DOUBLE PRECISION
[out]RT2I
          RT2I is DOUBLE PRECISION
          The real and imaginary parts of the eigenvalues. If the
          eigenvalues are a complex conjugate pair, RT1I > 0.
[out]CS
          CS is DOUBLE PRECISION
[out]SN
          SN is DOUBLE PRECISION
          Parameters of the rotation matrix.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
  Modified by V. Sima, Research Institute for Informatics, Bucharest,
  Romania, to reduce the risk of cancellation errors,
  when computing real eigenvalues, and to ensure, if possible, that
  abs(RT1R) >= abs(RT2R).

Definition at line 126 of file dlanv2.f.

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 DOUBLE PRECISION A, B, C, CS, D, RT1I, RT1R, RT2I, RT2R, SN
134* ..
135*
136* =====================================================================
137*
138* .. Parameters ..
139 DOUBLE PRECISION ZERO, HALF, ONE, TWO
140 parameter( zero = 0.0d+0, half = 0.5d+0, one = 1.0d+0,
141 $ two = 2.0d0 )
142 DOUBLE PRECISION MULTPL
143 parameter( multpl = 4.0d+0 )
144* ..
145* .. Local Scalars ..
146 DOUBLE PRECISION 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 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 safmin = dlamch( 'S' )
161 eps = dlamch( 'P' )
162 safmn2 = dlamch( 'B' )**int( log( safmin / eps ) /
163 $ log( dlamch( '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.sign( one, c ) )
182 $ 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 = dlapy2( 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 = dlapy2( 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 DLANV2
307*
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
double precision function dlapy2(x, y)
DLAPY2 returns sqrt(x2+y2).
Definition dlapy2.f:63
Here is the caller graph for this function: