LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Modules Pages
dlartgs.f
Go to the documentation of this file.
1*> \brief \b DLARTGS generates a plane rotation designed to introduce a bulge in implicit QR iteration for the bidiagonal SVD problem.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DLARTGS + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlartgs.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlartgs.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlartgs.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DLARTGS( X, Y, SIGMA, CS, SN )
20*
21* .. Scalar Arguments ..
22* DOUBLE PRECISION CS, SIGMA, SN, X, Y
23* ..
24*
25*
26*> \par Purpose:
27* =============
28*>
29*> \verbatim
30*>
31*> DLARTGS generates a plane rotation designed to introduce a bulge in
32*> Golub-Reinsch-style implicit QR iteration for the bidiagonal SVD
33*> problem. X and Y are the top-row entries, and SIGMA is the shift.
34*> The computed CS and SN define a plane rotation satisfying
35*>
36*> [ CS SN ] . [ X^2 - SIGMA ] = [ R ],
37*> [ -SN CS ] [ X * Y ] [ 0 ]
38*>
39*> with R nonnegative. If X^2 - SIGMA and X * Y are 0, then the
40*> rotation is by PI/2.
41*> \endverbatim
42*
43* Arguments:
44* ==========
45*
46*> \param[in] X
47*> \verbatim
48*> X is DOUBLE PRECISION
49*> The (1,1) entry of an upper bidiagonal matrix.
50*> \endverbatim
51*>
52*> \param[in] Y
53*> \verbatim
54*> Y is DOUBLE PRECISION
55*> The (1,2) entry of an upper bidiagonal matrix.
56*> \endverbatim
57*>
58*> \param[in] SIGMA
59*> \verbatim
60*> SIGMA is DOUBLE PRECISION
61*> The shift.
62*> \endverbatim
63*>
64*> \param[out] CS
65*> \verbatim
66*> CS is DOUBLE PRECISION
67*> The cosine of the rotation.
68*> \endverbatim
69*>
70*> \param[out] SN
71*> \verbatim
72*> SN is DOUBLE PRECISION
73*> The sine of the rotation.
74*> \endverbatim
75*
76* Authors:
77* ========
78*
79*> \author Univ. of Tennessee
80*> \author Univ. of California Berkeley
81*> \author Univ. of Colorado Denver
82*> \author NAG Ltd.
83*
84*> \ingroup lartgs
85*
86* =====================================================================
87 SUBROUTINE dlartgs( X, Y, SIGMA, CS, SN )
88*
89* -- LAPACK computational routine --
90* -- LAPACK is a software package provided by Univ. of Tennessee, --
91* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
92*
93* .. Scalar Arguments ..
94 DOUBLE PRECISION CS, SIGMA, SN, X, Y
95* ..
96*
97* ===================================================================
98*
99* .. Parameters ..
100 DOUBLE PRECISION NEGONE, ONE, ZERO
101 parameter( negone = -1.0d0, one = 1.0d0, zero = 0.0d0 )
102* ..
103* .. Local Scalars ..
104 DOUBLE PRECISION R, S, THRESH, W, Z
105* ..
106* .. External Subroutines ..
107 EXTERNAL dlartgp
108* ..
109* .. External Functions ..
110 DOUBLE PRECISION DLAMCH
111 EXTERNAL dlamch
112* .. Executable Statements ..
113*
114 thresh = dlamch('E')
115*
116* Compute the first column of B**T*B - SIGMA^2*I, up to a scale
117* factor.
118*
119 IF( (sigma .EQ. zero .AND. abs(x) .LT. thresh) .OR.
120 $ (abs(x) .EQ. sigma .AND. y .EQ. zero) ) THEN
121 z = zero
122 w = zero
123 ELSE IF( sigma .EQ. zero ) THEN
124 IF( x .GE. zero ) THEN
125 z = x
126 w = y
127 ELSE
128 z = -x
129 w = -y
130 END IF
131 ELSE IF( abs(x) .LT. thresh ) THEN
132 z = -sigma*sigma
133 w = zero
134 ELSE
135 IF( x .GE. zero ) THEN
136 s = one
137 ELSE
138 s = negone
139 END IF
140 z = s * (abs(x)-sigma) * (s+sigma/x)
141 w = s * y
142 END IF
143*
144* Generate the rotation.
145* CALL DLARTGP( Z, W, CS, SN, R ) might seem more natural;
146* reordering the arguments ensures that if Z = 0 then the rotation
147* is by PI/2.
148*
149 CALL dlartgp( w, z, sn, cs, r )
150*
151 RETURN
152*
153* End DLARTGS
154*
155 END
156
subroutine dlartgp(f, g, cs, sn, r)
DLARTGP generates a plane rotation so that the diagonal is nonnegative.
Definition dlartgp.f:93
subroutine dlartgs(x, y, sigma, cs, sn)
DLARTGS generates a plane rotation designed to introduce a bulge in implicit QR iteration for the bid...
Definition dlartgs.f:88