LAPACK  3.9.0
LAPACK: Linear Algebra PACKage

◆ 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.
Date
December 2016
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 129 of file dlanv2.f.

129 *
130 * -- LAPACK auxiliary routine (version 3.7.0) --
131 * -- LAPACK is a software package provided by Univ. of Tennessee, --
132 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
133 * December 2016
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 *
165  ELSE IF( b.EQ.zero ) THEN
166 *
167 * Swap rows and columns
168 *
169  cs = zero
170  sn = one
171  temp = d
172  d = a
173  a = temp
174  b = -c
175  c = zero
176 *
177  ELSE IF( ( a-d ).EQ.zero .AND. sign( one, b ).NE.sign( one, c ) )
178  $ THEN
179  cs = one
180  sn = zero
181 *
182  ELSE
183 *
184  temp = a - d
185  p = half*temp
186  bcmax = max( abs( b ), abs( c ) )
187  bcmis = min( abs( b ), abs( c ) )*sign( one, b )*sign( one, c )
188  scale = max( abs( p ), bcmax )
189  z = ( p / scale )*p + ( bcmax / scale )*bcmis
190 *
191 * If Z is of the order of the machine accuracy, postpone the
192 * decision on the nature of eigenvalues
193 *
194  IF( z.GE.multpl*eps ) THEN
195 *
196 * Real eigenvalues. Compute A and D.
197 *
198  z = p + sign( sqrt( scale )*sqrt( z ), p )
199  a = d + z
200  d = d - ( bcmax / z )*bcmis
201 *
202 * Compute B and the rotation matrix
203 *
204  tau = dlapy2( c, z )
205  cs = z / tau
206  sn = c / tau
207  b = b - c
208  c = zero
209 *
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 * Store eigenvalues in (RT1R,RT1I) and (RT2R,RT2I).
273 *
274  rt1r = a
275  rt2r = d
276  IF( c.EQ.zero ) THEN
277  rt1i = zero
278  rt2i = zero
279  ELSE
280  rt1i = sqrt( abs( b ) )*sqrt( abs( c ) )
281  rt2i = -rt1i
282  END IF
283  RETURN
284 *
285 * End of DLANV2
286 *
Here is the caller graph for this function:
dlapy2
double precision function dlapy2(X, Y)
DLAPY2 returns sqrt(x2+y2).
Definition: dlapy2.f:65
dlamch
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:70