LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zhptrd.f
Go to the documentation of this file.
1*> \brief \b ZHPTRD
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZHPTRD + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zhptrd.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zhptrd.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhptrd.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZHPTRD( UPLO, N, AP, D, E, TAU, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, N
24* ..
25* .. Array Arguments ..
26* DOUBLE PRECISION D( * ), E( * )
27* COMPLEX*16 AP( * ), TAU( * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> ZHPTRD reduces a complex Hermitian matrix A stored in packed form to
37*> real symmetric tridiagonal form T by a unitary similarity
38*> transformation: Q**H * A * Q = T.
39*> \endverbatim
40*
41* Arguments:
42* ==========
43*
44*> \param[in] UPLO
45*> \verbatim
46*> UPLO is CHARACTER*1
47*> = 'U': Upper triangle of A is stored;
48*> = 'L': Lower triangle of A is stored.
49*> \endverbatim
50*>
51*> \param[in] N
52*> \verbatim
53*> N is INTEGER
54*> The order of the matrix A. N >= 0.
55*> \endverbatim
56*>
57*> \param[in,out] AP
58*> \verbatim
59*> AP is COMPLEX*16 array, dimension (N*(N+1)/2)
60*> On entry, the upper or lower triangle of the Hermitian matrix
61*> A, packed columnwise in a linear array. The j-th column of A
62*> is stored in the array AP as follows:
63*> if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
64*> if UPLO = 'L', AP(i + (j-1)*(2*n-j)/2) = A(i,j) for j<=i<=n.
65*> On exit, if UPLO = 'U', the diagonal and first superdiagonal
66*> of A are overwritten by the corresponding elements of the
67*> tridiagonal matrix T, and the elements above the first
68*> superdiagonal, with the array TAU, represent the unitary
69*> matrix Q as a product of elementary reflectors; if UPLO
70*> = 'L', the diagonal and first subdiagonal of A are over-
71*> written by the corresponding elements of the tridiagonal
72*> matrix T, and the elements below the first subdiagonal, with
73*> the array TAU, represent the unitary matrix Q as a product
74*> of elementary reflectors. See Further Details.
75*> \endverbatim
76*>
77*> \param[out] D
78*> \verbatim
79*> D is DOUBLE PRECISION array, dimension (N)
80*> The diagonal elements of the tridiagonal matrix T:
81*> D(i) = A(i,i).
82*> \endverbatim
83*>
84*> \param[out] E
85*> \verbatim
86*> E is DOUBLE PRECISION array, dimension (N-1)
87*> The off-diagonal elements of the tridiagonal matrix T:
88*> E(i) = A(i,i+1) if UPLO = 'U', E(i) = A(i+1,i) if UPLO = 'L'.
89*> \endverbatim
90*>
91*> \param[out] TAU
92*> \verbatim
93*> TAU is COMPLEX*16 array, dimension (N-1)
94*> The scalar factors of the elementary reflectors (see Further
95*> Details).
96*> \endverbatim
97*>
98*> \param[out] INFO
99*> \verbatim
100*> INFO is INTEGER
101*> = 0: successful exit
102*> < 0: if INFO = -i, the i-th argument had an illegal value
103*> \endverbatim
104*
105* Authors:
106* ========
107*
108*> \author Univ. of Tennessee
109*> \author Univ. of California Berkeley
110*> \author Univ. of Colorado Denver
111*> \author NAG Ltd.
112*
113*> \ingroup hptrd
114*
115*> \par Further Details:
116* =====================
117*>
118*> \verbatim
119*>
120*> If UPLO = 'U', the matrix Q is represented as a product of elementary
121*> reflectors
122*>
123*> Q = H(n-1) . . . H(2) H(1).
124*>
125*> Each H(i) has the form
126*>
127*> H(i) = I - tau * v * v**H
128*>
129*> where tau is a complex scalar, and v is a complex vector with
130*> v(i+1:n) = 0 and v(i) = 1; v(1:i-1) is stored on exit in AP,
131*> overwriting A(1:i-1,i+1), and tau is stored in TAU(i).
132*>
133*> If UPLO = 'L', the matrix Q is represented as a product of elementary
134*> reflectors
135*>
136*> Q = H(1) H(2) . . . H(n-1).
137*>
138*> Each H(i) has the form
139*>
140*> H(i) = I - tau * v * v**H
141*>
142*> where tau is a complex scalar, and v is a complex vector with
143*> v(1:i) = 0 and v(i+1) = 1; v(i+2:n) is stored on exit in AP,
144*> overwriting A(i+2:n,i), and tau is stored in TAU(i).
145*> \endverbatim
146*>
147* =====================================================================
148 SUBROUTINE zhptrd( UPLO, N, AP, D, E, TAU, INFO )
149*
150* -- LAPACK computational routine --
151* -- LAPACK is a software package provided by Univ. of Tennessee, --
152* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
153*
154* .. Scalar Arguments ..
155 CHARACTER UPLO
156 INTEGER INFO, N
157* ..
158* .. Array Arguments ..
159 DOUBLE PRECISION D( * ), E( * )
160 COMPLEX*16 AP( * ), TAU( * )
161* ..
162*
163* =====================================================================
164*
165* .. Parameters ..
166 COMPLEX*16 ONE, ZERO, HALF
167 parameter( one = ( 1.0d+0, 0.0d+0 ),
168 $ zero = ( 0.0d+0, 0.0d+0 ),
169 $ half = ( 0.5d+0, 0.0d+0 ) )
170* ..
171* .. Local Scalars ..
172 LOGICAL UPPER
173 INTEGER I, I1, I1I1, II
174 COMPLEX*16 ALPHA, TAUI
175* ..
176* .. External Subroutines ..
177 EXTERNAL xerbla, zaxpy, zhpmv, zhpr2, zlarfg
178* ..
179* .. External Functions ..
180 LOGICAL LSAME
181 COMPLEX*16 ZDOTC
182 EXTERNAL lsame, zdotc
183* ..
184* .. Intrinsic Functions ..
185 INTRINSIC dble
186* ..
187* .. Executable Statements ..
188*
189* Test the input parameters
190*
191 info = 0
192 upper = lsame( uplo, 'U' )
193 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
194 info = -1
195 ELSE IF( n.LT.0 ) THEN
196 info = -2
197 END IF
198 IF( info.NE.0 ) THEN
199 CALL xerbla( 'ZHPTRD', -info )
200 RETURN
201 END IF
202*
203* Quick return if possible
204*
205 IF( n.LE.0 )
206 $ RETURN
207*
208 IF( upper ) THEN
209*
210* Reduce the upper triangle of A.
211* I1 is the index in AP of A(1,I+1).
212*
213 i1 = n*( n-1 ) / 2 + 1
214 ap( i1+n-1 ) = dble( ap( i1+n-1 ) )
215 DO 10 i = n - 1, 1, -1
216*
217* Generate elementary reflector H(i) = I - tau * v * v**H
218* to annihilate A(1:i-1,i+1)
219*
220 alpha = ap( i1+i-1 )
221 CALL zlarfg( i, alpha, ap( i1 ), 1, taui )
222 e( i ) = dble( alpha )
223*
224 IF( taui.NE.zero ) THEN
225*
226* Apply H(i) from both sides to A(1:i,1:i)
227*
228 ap( i1+i-1 ) = one
229*
230* Compute y := tau * A * v storing y in TAU(1:i)
231*
232 CALL zhpmv( uplo, i, taui, ap, ap( i1 ), 1, zero, tau,
233 $ 1 )
234*
235* Compute w := y - 1/2 * tau * (y**H *v) * v
236*
237 alpha = -half*taui*zdotc( i, tau, 1, ap( i1 ), 1 )
238 CALL zaxpy( i, alpha, ap( i1 ), 1, tau, 1 )
239*
240* Apply the transformation as a rank-2 update:
241* A := A - v * w**H - w * v**H
242*
243 CALL zhpr2( uplo, i, -one, ap( i1 ), 1, tau, 1, ap )
244*
245 END IF
246 ap( i1+i-1 ) = e( i )
247 d( i+1 ) = dble( ap( i1+i ) )
248 tau( i ) = taui
249 i1 = i1 - i
250 10 CONTINUE
251 d( 1 ) = dble( ap( 1 ) )
252 ELSE
253*
254* Reduce the lower triangle of A. II is the index in AP of
255* A(i,i) and I1I1 is the index of A(i+1,i+1).
256*
257 ii = 1
258 ap( 1 ) = dble( ap( 1 ) )
259 DO 20 i = 1, n - 1
260 i1i1 = ii + n - i + 1
261*
262* Generate elementary reflector H(i) = I - tau * v * v**H
263* to annihilate A(i+2:n,i)
264*
265 alpha = ap( ii+1 )
266 CALL zlarfg( n-i, alpha, ap( ii+2 ), 1, taui )
267 e( i ) = dble( alpha )
268*
269 IF( taui.NE.zero ) THEN
270*
271* Apply H(i) from both sides to A(i+1:n,i+1:n)
272*
273 ap( ii+1 ) = one
274*
275* Compute y := tau * A * v storing y in TAU(i:n-1)
276*
277 CALL zhpmv( uplo, n-i, taui, ap( i1i1 ), ap( ii+1 ),
278 $ 1,
279 $ zero, tau( i ), 1 )
280*
281* Compute w := y - 1/2 * tau * (y**H *v) * v
282*
283 alpha = -half*taui*zdotc( n-i, tau( i ), 1,
284 $ ap( ii+1 ),
285 $ 1 )
286 CALL zaxpy( n-i, alpha, ap( ii+1 ), 1, tau( i ), 1 )
287*
288* Apply the transformation as a rank-2 update:
289* A := A - v * w**H - w * v**H
290*
291 CALL zhpr2( uplo, n-i, -one, ap( ii+1 ), 1, tau( i ),
292 $ 1,
293 $ ap( i1i1 ) )
294*
295 END IF
296 ap( ii+1 ) = e( i )
297 d( i ) = dble( ap( ii ) )
298 tau( i ) = taui
299 ii = i1i1
300 20 CONTINUE
301 d( n ) = dble( ap( ii ) )
302 END IF
303*
304 RETURN
305*
306* End of ZHPTRD
307*
308 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zaxpy(n, za, zx, incx, zy, incy)
ZAXPY
Definition zaxpy.f:88
subroutine zhpmv(uplo, n, alpha, ap, x, incx, beta, y, incy)
ZHPMV
Definition zhpmv.f:149
subroutine zhpr2(uplo, n, alpha, x, incx, y, incy, ap)
ZHPR2
Definition zhpr2.f:145
subroutine zhptrd(uplo, n, ap, d, e, tau, info)
ZHPTRD
Definition zhptrd.f:149
subroutine zlarfg(n, alpha, x, incx, tau)
ZLARFG generates an elementary reflector (Householder matrix).
Definition zlarfg.f:104