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

◆ dlasv2()

subroutine dlasv2 ( double precision  f,
double precision  g,
double precision  h,
double precision  ssmin,
double precision  ssmax,
double precision  snr,
double precision  csr,
double precision  snl,
double precision  csl 
)

DLASV2 computes the singular value decomposition of a 2-by-2 triangular matrix.

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

Purpose:
 DLASV2 computes the singular value decomposition of a 2-by-2
 triangular matrix
    [  F   G  ]
    [  0   H  ].
 On return, abs(SSMAX) is the larger singular value, abs(SSMIN) is the
 smaller singular value, and (CSL,SNL) and (CSR,SNR) are the left and
 right singular vectors for abs(SSMAX), giving the decomposition

    [ CSL  SNL ] [  F   G  ] [ CSR -SNR ]  =  [ SSMAX   0   ]
    [-SNL  CSL ] [  0   H  ] [ SNR  CSR ]     [  0    SSMIN ].
Parameters
[in]F
          F is DOUBLE PRECISION
          The (1,1) element of the 2-by-2 matrix.
[in]G
          G is DOUBLE PRECISION
          The (1,2) element of the 2-by-2 matrix.
[in]H
          H is DOUBLE PRECISION
          The (2,2) element of the 2-by-2 matrix.
[out]SSMIN
          SSMIN is DOUBLE PRECISION
          abs(SSMIN) is the smaller singular value.
[out]SSMAX
          SSMAX is DOUBLE PRECISION
          abs(SSMAX) is the larger singular value.
[out]SNL
          SNL is DOUBLE PRECISION
[out]CSL
          CSL is DOUBLE PRECISION
          The vector (CSL, SNL) is a unit left singular vector for the
          singular value abs(SSMAX).
[out]SNR
          SNR is DOUBLE PRECISION
[out]CSR
          CSR is DOUBLE PRECISION
          The vector (CSR, SNR) is a unit right singular vector for the
          singular value abs(SSMAX).
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
  Any input parameter may be aliased with any output parameter.

  Barring over/underflow and assuming a guard digit in subtraction, all
  output quantities are correct to within a few units in the last
  place (ulps).

  In IEEE arithmetic, the code works correctly if one matrix element is
  infinite.

  Overflow will not occur unless the largest singular value itself
  overflows or is within a few ulps of overflow.

  Underflow is harmless if underflow is gradual. Otherwise, results
  may correspond to a matrix modified by perturbations of size near
  the underflow threshold.

Definition at line 135 of file dlasv2.f.

136*
137* -- LAPACK auxiliary routine --
138* -- LAPACK is a software package provided by Univ. of Tennessee, --
139* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
140*
141* .. Scalar Arguments ..
142 DOUBLE PRECISION CSL, CSR, F, G, H, SNL, SNR, SSMAX, SSMIN
143* ..
144*
145* =====================================================================
146*
147* .. Parameters ..
148 DOUBLE PRECISION ZERO
149 parameter( zero = 0.0d0 )
150 DOUBLE PRECISION HALF
151 parameter( half = 0.5d0 )
152 DOUBLE PRECISION ONE
153 parameter( one = 1.0d0 )
154 DOUBLE PRECISION TWO
155 parameter( two = 2.0d0 )
156 DOUBLE PRECISION FOUR
157 parameter( four = 4.0d0 )
158* ..
159* .. Local Scalars ..
160 LOGICAL GASMAL, SWAP
161 INTEGER PMAX
162 DOUBLE PRECISION A, CLT, CRT, D, FA, FT, GA, GT, HA, HT, L, M,
163 $ MM, R, S, SLT, SRT, T, TEMP, TSIGN, TT
164* ..
165* .. Intrinsic Functions ..
166 INTRINSIC abs, sign, sqrt
167* ..
168* .. External Functions ..
169 DOUBLE PRECISION DLAMCH
170 EXTERNAL dlamch
171* ..
172* .. Executable Statements ..
173*
174 ft = f
175 fa = abs( ft )
176 ht = h
177 ha = abs( h )
178*
179* PMAX points to the maximum absolute element of matrix
180* PMAX = 1 if F largest in absolute values
181* PMAX = 2 if G largest in absolute values
182* PMAX = 3 if H largest in absolute values
183*
184 pmax = 1
185 swap = ( ha.GT.fa )
186 IF( swap ) THEN
187 pmax = 3
188 temp = ft
189 ft = ht
190 ht = temp
191 temp = fa
192 fa = ha
193 ha = temp
194*
195* Now FA .ge. HA
196*
197 END IF
198 gt = g
199 ga = abs( gt )
200 IF( ga.EQ.zero ) THEN
201*
202* Diagonal matrix
203*
204 ssmin = ha
205 ssmax = fa
206 clt = one
207 crt = one
208 slt = zero
209 srt = zero
210 ELSE
211 gasmal = .true.
212 IF( ga.GT.fa ) THEN
213 pmax = 2
214 IF( ( fa / ga ).LT.dlamch( 'EPS' ) ) THEN
215*
216* Case of very large GA
217*
218 gasmal = .false.
219 ssmax = ga
220 IF( ha.GT.one ) THEN
221 ssmin = fa / ( ga / ha )
222 ELSE
223 ssmin = ( fa / ga )*ha
224 END IF
225 clt = one
226 slt = ht / gt
227 srt = one
228 crt = ft / gt
229 END IF
230 END IF
231 IF( gasmal ) THEN
232*
233* Normal case
234*
235 d = fa - ha
236 IF( d.EQ.fa ) THEN
237*
238* Copes with infinite F or H
239*
240 l = one
241 ELSE
242 l = d / fa
243 END IF
244*
245* Note that 0 .le. L .le. 1
246*
247 m = gt / ft
248*
249* Note that abs(M) .le. 1/macheps
250*
251 t = two - l
252*
253* Note that T .ge. 1
254*
255 mm = m*m
256 tt = t*t
257 s = sqrt( tt+mm )
258*
259* Note that 1 .le. S .le. 1 + 1/macheps
260*
261 IF( l.EQ.zero ) THEN
262 r = abs( m )
263 ELSE
264 r = sqrt( l*l+mm )
265 END IF
266*
267* Note that 0 .le. R .le. 1 + 1/macheps
268*
269 a = half*( s+r )
270*
271* Note that 1 .le. A .le. 1 + abs(M)
272*
273 ssmin = ha / a
274 ssmax = fa*a
275 IF( mm.EQ.zero ) THEN
276*
277* Note that M is very tiny
278*
279 IF( l.EQ.zero ) THEN
280 t = sign( two, ft )*sign( one, gt )
281 ELSE
282 t = gt / sign( d, ft ) + m / t
283 END IF
284 ELSE
285 t = ( m / ( s+t )+m / ( r+l ) )*( one+a )
286 END IF
287 l = sqrt( t*t+four )
288 crt = two / l
289 srt = t / l
290 clt = ( crt+srt*m ) / a
291 slt = ( ht / ft )*srt / a
292 END IF
293 END IF
294 IF( swap ) THEN
295 csl = srt
296 snl = crt
297 csr = slt
298 snr = clt
299 ELSE
300 csl = clt
301 snl = slt
302 csr = crt
303 snr = srt
304 END IF
305*
306* Correct signs of SSMAX and SSMIN
307*
308 IF( pmax.EQ.1 )
309 $ tsign = sign( one, csr )*sign( one, csl )*sign( one, f )
310 IF( pmax.EQ.2 )
311 $ tsign = sign( one, snr )*sign( one, csl )*sign( one, g )
312 IF( pmax.EQ.3 )
313 $ tsign = sign( one, snr )*sign( one, snl )*sign( one, h )
314 ssmax = sign( ssmax, tsign )
315 ssmin = sign( ssmin, tsign*sign( one, f )*sign( one, h ) )
316 RETURN
317*
318* End of DLASV2
319*
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
Here is the caller graph for this function: