LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zhpgst.f
Go to the documentation of this file.
1*> \brief \b ZHPGST
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZHPGST + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zhpgst.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zhpgst.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhpgst.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZHPGST( ITYPE, UPLO, N, AP, BP, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, ITYPE, N
24* ..
25* .. Array Arguments ..
26* COMPLEX*16 AP( * ), BP( * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> ZHPGST reduces a complex Hermitian-definite generalized
36*> eigenproblem to standard form, using packed storage.
37*>
38*> If ITYPE = 1, the problem is A*x = lambda*B*x,
39*> and A is overwritten by inv(U**H)*A*inv(U) or inv(L)*A*inv(L**H)
40*>
41*> If ITYPE = 2 or 3, the problem is A*B*x = lambda*x or
42*> B*A*x = lambda*x, and A is overwritten by U*A*U**H or L**H*A*L.
43*>
44*> B must have been previously factorized as U**H*U or L*L**H by ZPPTRF.
45*> \endverbatim
46*
47* Arguments:
48* ==========
49*
50*> \param[in] ITYPE
51*> \verbatim
52*> ITYPE is INTEGER
53*> = 1: compute inv(U**H)*A*inv(U) or inv(L)*A*inv(L**H);
54*> = 2 or 3: compute U*A*U**H or L**H*A*L.
55*> \endverbatim
56*>
57*> \param[in] UPLO
58*> \verbatim
59*> UPLO is CHARACTER*1
60*> = 'U': Upper triangle of A is stored and B is factored as
61*> U**H*U;
62*> = 'L': Lower triangle of A is stored and B is factored as
63*> L*L**H.
64*> \endverbatim
65*>
66*> \param[in] N
67*> \verbatim
68*> N is INTEGER
69*> The order of the matrices A and B. N >= 0.
70*> \endverbatim
71*>
72*> \param[in,out] AP
73*> \verbatim
74*> AP is COMPLEX*16 array, dimension (N*(N+1)/2)
75*> On entry, the upper or lower triangle of the Hermitian matrix
76*> A, packed columnwise in a linear array. The j-th column of A
77*> is stored in the array AP as follows:
78*> if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
79*> if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
80*>
81*> On exit, if INFO = 0, the transformed matrix, stored in the
82*> same format as A.
83*> \endverbatim
84*>
85*> \param[in] BP
86*> \verbatim
87*> BP is COMPLEX*16 array, dimension (N*(N+1)/2)
88*> The triangular factor from the Cholesky factorization of B,
89*> stored in the same format as A, as returned by ZPPTRF.
90*> \endverbatim
91*>
92*> \param[out] INFO
93*> \verbatim
94*> INFO is INTEGER
95*> = 0: successful exit
96*> < 0: if INFO = -i, the i-th argument had an illegal value
97*> \endverbatim
98*
99* Authors:
100* ========
101*
102*> \author Univ. of Tennessee
103*> \author Univ. of California Berkeley
104*> \author Univ. of Colorado Denver
105*> \author NAG Ltd.
106*
107*> \ingroup hpgst
108*
109* =====================================================================
110 SUBROUTINE zhpgst( ITYPE, UPLO, N, AP, BP, INFO )
111*
112* -- LAPACK computational routine --
113* -- LAPACK is a software package provided by Univ. of Tennessee, --
114* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
115*
116* .. Scalar Arguments ..
117 CHARACTER UPLO
118 INTEGER INFO, ITYPE, N
119* ..
120* .. Array Arguments ..
121 COMPLEX*16 AP( * ), BP( * )
122* ..
123*
124* =====================================================================
125*
126* .. Parameters ..
127 DOUBLE PRECISION ONE, HALF
128 parameter( one = 1.0d+0, half = 0.5d+0 )
129 COMPLEX*16 CONE
130 parameter( cone = ( 1.0d+0, 0.0d+0 ) )
131* ..
132* .. Local Scalars ..
133 LOGICAL UPPER
134 INTEGER J, J1, J1J1, JJ, K, K1, K1K1, KK
135 DOUBLE PRECISION AJJ, AKK, BJJ, BKK
136 COMPLEX*16 CT
137* ..
138* .. External Subroutines ..
139 EXTERNAL xerbla, zaxpy, zdscal, zhpmv, zhpr2,
140 $ ztpmv,
141 $ ztpsv
142* ..
143* .. Intrinsic Functions ..
144 INTRINSIC dble
145* ..
146* .. External Functions ..
147 LOGICAL LSAME
148 COMPLEX*16 ZDOTC
149 EXTERNAL lsame, zdotc
150* ..
151* .. Executable Statements ..
152*
153* Test the input parameters.
154*
155 info = 0
156 upper = lsame( uplo, 'U' )
157 IF( itype.LT.1 .OR. itype.GT.3 ) THEN
158 info = -1
159 ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
160 info = -2
161 ELSE IF( n.LT.0 ) THEN
162 info = -3
163 END IF
164 IF( info.NE.0 ) THEN
165 CALL xerbla( 'ZHPGST', -info )
166 RETURN
167 END IF
168*
169 IF( itype.EQ.1 ) THEN
170 IF( upper ) THEN
171*
172* Compute inv(U**H)*A*inv(U)
173*
174* J1 and JJ are the indices of A(1,j) and A(j,j)
175*
176 jj = 0
177 DO 10 j = 1, n
178 j1 = jj + 1
179 jj = jj + j
180*
181* Compute the j-th column of the upper triangle of A
182*
183 ap( jj ) = dble( ap( jj ) )
184 bjj = dble( bp( jj ) )
185 CALL ztpsv( uplo, 'Conjugate transpose', 'Non-unit',
186 $ j,
187 $ bp, ap( j1 ), 1 )
188 CALL zhpmv( uplo, j-1, -cone, ap, bp( j1 ), 1, cone,
189 $ ap( j1 ), 1 )
190 CALL zdscal( j-1, one / bjj, ap( j1 ), 1 )
191 ap( jj ) = ( ap( jj )-zdotc( j-1, ap( j1 ), 1,
192 $ bp( j1 ),
193 $ 1 ) ) / bjj
194 10 CONTINUE
195 ELSE
196*
197* Compute inv(L)*A*inv(L**H)
198*
199* KK and K1K1 are the indices of A(k,k) and A(k+1,k+1)
200*
201 kk = 1
202 DO 20 k = 1, n
203 k1k1 = kk + n - k + 1
204*
205* Update the lower triangle of A(k:n,k:n)
206*
207 akk = dble( ap( kk ) )
208 bkk = dble( bp( kk ) )
209 akk = akk / bkk**2
210 ap( kk ) = akk
211 IF( k.LT.n ) THEN
212 CALL zdscal( n-k, one / bkk, ap( kk+1 ), 1 )
213 ct = -half*akk
214 CALL zaxpy( n-k, ct, bp( kk+1 ), 1, ap( kk+1 ), 1 )
215 CALL zhpr2( uplo, n-k, -cone, ap( kk+1 ), 1,
216 $ bp( kk+1 ), 1, ap( k1k1 ) )
217 CALL zaxpy( n-k, ct, bp( kk+1 ), 1, ap( kk+1 ), 1 )
218 CALL ztpsv( uplo, 'No transpose', 'Non-unit', n-k,
219 $ bp( k1k1 ), ap( kk+1 ), 1 )
220 END IF
221 kk = k1k1
222 20 CONTINUE
223 END IF
224 ELSE
225 IF( upper ) THEN
226*
227* Compute U*A*U**H
228*
229* K1 and KK are the indices of A(1,k) and A(k,k)
230*
231 kk = 0
232 DO 30 k = 1, n
233 k1 = kk + 1
234 kk = kk + k
235*
236* Update the upper triangle of A(1:k,1:k)
237*
238 akk = dble( ap( kk ) )
239 bkk = dble( bp( kk ) )
240 CALL ztpmv( uplo, 'No transpose', 'Non-unit', k-1, bp,
241 $ ap( k1 ), 1 )
242 ct = half*akk
243 CALL zaxpy( k-1, ct, bp( k1 ), 1, ap( k1 ), 1 )
244 CALL zhpr2( uplo, k-1, cone, ap( k1 ), 1, bp( k1 ), 1,
245 $ ap )
246 CALL zaxpy( k-1, ct, bp( k1 ), 1, ap( k1 ), 1 )
247 CALL zdscal( k-1, bkk, ap( k1 ), 1 )
248 ap( kk ) = akk*bkk**2
249 30 CONTINUE
250 ELSE
251*
252* Compute L**H *A*L
253*
254* JJ and J1J1 are the indices of A(j,j) and A(j+1,j+1)
255*
256 jj = 1
257 DO 40 j = 1, n
258 j1j1 = jj + n - j + 1
259*
260* Compute the j-th column of the lower triangle of A
261*
262 ajj = dble( ap( jj ) )
263 bjj = dble( bp( jj ) )
264 ap( jj ) = ajj*bjj + zdotc( n-j, ap( jj+1 ), 1,
265 $ bp( jj+1 ), 1 )
266 CALL zdscal( n-j, bjj, ap( jj+1 ), 1 )
267 CALL zhpmv( uplo, n-j, cone, ap( j1j1 ), bp( jj+1 ),
268 $ 1,
269 $ cone, ap( jj+1 ), 1 )
270 CALL ztpmv( uplo, 'Conjugate transpose', 'Non-unit',
271 $ n-j+1, bp( jj ), ap( jj ), 1 )
272 jj = j1j1
273 40 CONTINUE
274 END IF
275 END IF
276 RETURN
277*
278* End of ZHPGST
279*
280 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zaxpy(n, za, zx, incx, zy, incy)
ZAXPY
Definition zaxpy.f:88
subroutine zhpgst(itype, uplo, n, ap, bp, info)
ZHPGST
Definition zhpgst.f:111
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 zdscal(n, da, zx, incx)
ZDSCAL
Definition zdscal.f:78
subroutine ztpmv(uplo, trans, diag, n, ap, x, incx)
ZTPMV
Definition ztpmv.f:142
subroutine ztpsv(uplo, trans, diag, n, ap, x, incx)
ZTPSV
Definition ztpsv.f:144