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