LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
slaqr1.f
Go to the documentation of this file.
1*> \brief \b SLAQR1 sets a scalar multiple of the first column of the product of 2-by-2 or 3-by-3 matrix H and specified shifts.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download SLAQR1 + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slaqr1.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slaqr1.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slaqr1.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE SLAQR1( N, H, LDH, SR1, SI1, SR2, SI2, V )
20*
21* .. Scalar Arguments ..
22* REAL SI1, SI2, SR1, SR2
23* INTEGER LDH, N
24* ..
25* .. Array Arguments ..
26* REAL H( LDH, * ), V( * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> Given a 2-by-2 or 3-by-3 matrix H, SLAQR1 sets v to a
36*> scalar multiple of the first column of the product
37*>
38*> (*) K = (H - (sr1 + i*si1)*I)*(H - (sr2 + i*si2)*I)
39*>
40*> scaling to avoid overflows and most underflows. It
41*> is assumed that either
42*>
43*> 1) sr1 = sr2 and si1 = -si2
44*> or
45*> 2) si1 = si2 = 0.
46*>
47*> This is useful for starting double implicit shift bulges
48*> in the QR algorithm.
49*> \endverbatim
50*
51* Arguments:
52* ==========
53*
54*> \param[in] N
55*> \verbatim
56*> N is INTEGER
57*> Order of the matrix H. N must be either 2 or 3.
58*> \endverbatim
59*>
60*> \param[in] H
61*> \verbatim
62*> H is REAL array, dimension (LDH,N)
63*> The 2-by-2 or 3-by-3 matrix H in (*).
64*> \endverbatim
65*>
66*> \param[in] LDH
67*> \verbatim
68*> LDH is INTEGER
69*> The leading dimension of H as declared in
70*> the calling procedure. LDH >= N
71*> \endverbatim
72*>
73*> \param[in] SR1
74*> \verbatim
75*> SR1 is REAL
76*> \endverbatim
77*>
78*> \param[in] SI1
79*> \verbatim
80*> SI1 is REAL
81*> \endverbatim
82*>
83*> \param[in] SR2
84*> \verbatim
85*> SR2 is REAL
86*> \endverbatim
87*>
88*> \param[in] SI2
89*> \verbatim
90*> SI2 is REAL
91*> The shifts in (*).
92*> \endverbatim
93*>
94*> \param[out] V
95*> \verbatim
96*> V is REAL array, dimension (N)
97*> A scalar multiple of the first column of the
98*> matrix K in (*).
99*> \endverbatim
100*
101* Authors:
102* ========
103*
104*> \author Univ. of Tennessee
105*> \author Univ. of California Berkeley
106*> \author Univ. of Colorado Denver
107*> \author NAG Ltd.
108*
109*> \ingroup laqr1
110*
111*> \par Contributors:
112* ==================
113*>
114*> Karen Braman and Ralph Byers, Department of Mathematics,
115*> University of Kansas, USA
116*>
117* =====================================================================
118 SUBROUTINE slaqr1( N, H, LDH, SR1, SI1, SR2, SI2, V )
119*
120* -- LAPACK auxiliary routine --
121* -- LAPACK is a software package provided by Univ. of Tennessee, --
122* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
123*
124* .. Scalar Arguments ..
125 REAL SI1, SI2, SR1, SR2
126 INTEGER LDH, N
127* ..
128* .. Array Arguments ..
129 REAL H( LDH, * ), V( * )
130* ..
131*
132* ================================================================
133*
134* .. Parameters ..
135 REAL ZERO
136 parameter( zero = 0.0e0 )
137* ..
138* .. Local Scalars ..
139 REAL H21S, H31S, S
140* ..
141* .. Intrinsic Functions ..
142 INTRINSIC abs
143* ..
144* .. Executable Statements ..
145*
146* Quick return if possible
147*
148 IF( n.NE.2 .AND. n.NE.3 ) THEN
149 RETURN
150 END IF
151*
152 IF( n.EQ.2 ) THEN
153 s = abs( h( 1, 1 )-sr2 ) + abs( si2 ) + abs( h( 2, 1 ) )
154 IF( s.EQ.zero ) THEN
155 v( 1 ) = zero
156 v( 2 ) = zero
157 ELSE
158 h21s = h( 2, 1 ) / s
159 v( 1 ) = h21s*h( 1, 2 ) + ( h( 1, 1 )-sr1 )*
160 $ ( ( h( 1, 1 )-sr2 ) / s ) - si1*( si2 / s )
161 v( 2 ) = h21s*( h( 1, 1 )+h( 2, 2 )-sr1-sr2 )
162 END IF
163 ELSE
164 s = abs( h( 1, 1 )-sr2 ) + abs( si2 ) + abs( h( 2, 1 ) ) +
165 $ abs( h( 3, 1 ) )
166 IF( s.EQ.zero ) THEN
167 v( 1 ) = zero
168 v( 2 ) = zero
169 v( 3 ) = zero
170 ELSE
171 h21s = h( 2, 1 ) / s
172 h31s = h( 3, 1 ) / s
173 v( 1 ) = ( h( 1, 1 )-sr1 )*( ( h( 1, 1 )-sr2 ) / s ) -
174 $ si1*( si2 / s ) + h( 1, 2 )*h21s + h( 1, 3 )*h31s
175 v( 2 ) = h21s*( h( 1, 1 )+h( 2, 2 )-sr1-sr2 ) +
176 $ h( 2, 3 )*h31s
177 v( 3 ) = h31s*( h( 1, 1 )+h( 3, 3 )-sr1-sr2 ) +
178 $ h21s*h( 3, 2 )
179 END IF
180 END IF
181 END
subroutine slaqr1(n, h, ldh, sr1, si1, sr2, si2, v)
SLAQR1 sets a scalar multiple of the first column of the product of 2-by-2 or 3-by-3 matrix H and spe...
Definition slaqr1.f:119