LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ chpgst()

subroutine chpgst ( integer itype,
character uplo,
integer n,
complex, dimension( * ) ap,
complex, dimension( * ) bp,
integer info )

CHPGST

Download CHPGST + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> CHPGST reduces a complex Hermitian-definite generalized
!> eigenproblem to standard form, using packed storage.
!>
!> If ITYPE = 1, the problem is A*x = lambda*B*x,
!> and A is overwritten by inv(U**H)*A*inv(U) or inv(L)*A*inv(L**H)
!>
!> If ITYPE = 2 or 3, the problem is A*B*x = lambda*x or
!> B*A*x = lambda*x, and A is overwritten by U*A*U**H or L**H*A*L.
!>
!> B must have been previously factorized as U**H*U or L*L**H by CPPTRF.
!> 
Parameters
[in]ITYPE
!>          ITYPE is INTEGER
!>          = 1: compute inv(U**H)*A*inv(U) or inv(L)*A*inv(L**H);
!>          = 2 or 3: compute U*A*U**H or L**H*A*L.
!> 
[in]UPLO
!>          UPLO is CHARACTER*1
!>          = 'U':  Upper triangle of A is stored and B is factored as
!>                  U**H*U;
!>          = 'L':  Lower triangle of A is stored and B is factored as
!>                  L*L**H.
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrices A and B.  N >= 0.
!> 
[in,out]AP
!>          AP is COMPLEX array, dimension (N*(N+1)/2)
!>          On entry, the upper or lower triangle of the Hermitian matrix
!>          A, packed columnwise in a linear array.  The j-th column of A
!>          is stored in the array AP as follows:
!>          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
!>          if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
!>
!>          On exit, if INFO = 0, the transformed matrix, stored in the
!>          same format as A.
!> 
[in]BP
!>          BP is COMPLEX array, dimension (N*(N+1)/2)
!>          The triangular factor from the Cholesky factorization of B,
!>          stored in the same format as A, as returned by CPPTRF.
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0:  successful exit
!>          < 0:  if INFO = -i, the i-th argument had an illegal value
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 110 of file chpgst.f.

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 AP( * ), BP( * )
122* ..
123*
124* =====================================================================
125*
126* .. Parameters ..
127 REAL ONE, HALF
128 parameter( one = 1.0e+0, half = 0.5e+0 )
129 COMPLEX CONE
130 parameter( cone = ( 1.0e+0, 0.0e+0 ) )
131* ..
132* .. Local Scalars ..
133 LOGICAL UPPER
134 INTEGER J, J1, J1J1, JJ, K, K1, K1K1, KK
135 REAL AJJ, AKK, BJJ, BKK
136 COMPLEX CT
137* ..
138* .. External Subroutines ..
139 EXTERNAL caxpy, chpmv, chpr2, csscal, ctpmv,
140 $ ctpsv,
141 $ xerbla
142* ..
143* .. Intrinsic Functions ..
144 INTRINSIC real
145* ..
146* .. External Functions ..
147 LOGICAL LSAME
148 COMPLEX CDOTC
149 EXTERNAL lsame, cdotc
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( 'CHPGST', -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 ) = real( ap( jj ) )
184 bjj = real( bp( jj ) )
185 CALL ctpsv( uplo, 'Conjugate transpose', 'Non-unit',
186 $ j,
187 $ bp, ap( j1 ), 1 )
188 CALL chpmv( uplo, j-1, -cone, ap, bp( j1 ), 1, cone,
189 $ ap( j1 ), 1 )
190 CALL csscal( j-1, one / bjj, ap( j1 ), 1 )
191 ap( jj ) = ( ap( jj )-cdotc( 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 = real( ap( kk ) )
208 bkk = real( bp( kk ) )
209 akk = akk / bkk**2
210 ap( kk ) = akk
211 IF( k.LT.n ) THEN
212 CALL csscal( n-k, one / bkk, ap( kk+1 ), 1 )
213 ct = -half*akk
214 CALL caxpy( n-k, ct, bp( kk+1 ), 1, ap( kk+1 ), 1 )
215 CALL chpr2( uplo, n-k, -cone, ap( kk+1 ), 1,
216 $ bp( kk+1 ), 1, ap( k1k1 ) )
217 CALL caxpy( n-k, ct, bp( kk+1 ), 1, ap( kk+1 ), 1 )
218 CALL ctpsv( 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 = real( ap( kk ) )
239 bkk = real( bp( kk ) )
240 CALL ctpmv( uplo, 'No transpose', 'Non-unit', k-1, bp,
241 $ ap( k1 ), 1 )
242 ct = half*akk
243 CALL caxpy( k-1, ct, bp( k1 ), 1, ap( k1 ), 1 )
244 CALL chpr2( uplo, k-1, cone, ap( k1 ), 1, bp( k1 ), 1,
245 $ ap )
246 CALL caxpy( k-1, ct, bp( k1 ), 1, ap( k1 ), 1 )
247 CALL csscal( 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 = real( ap( jj ) )
263 bjj = real( bp( jj ) )
264 ap( jj ) = ajj*bjj + cdotc( n-j, ap( jj+1 ), 1,
265 $ bp( jj+1 ), 1 )
266 CALL csscal( n-j, bjj, ap( jj+1 ), 1 )
267 CALL chpmv( uplo, n-j, cone, ap( j1j1 ), bp( jj+1 ),
268 $ 1,
269 $ cone, ap( jj+1 ), 1 )
270 CALL ctpmv( 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 CHPGST
279*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine caxpy(n, ca, cx, incx, cy, incy)
CAXPY
Definition caxpy.f:88
complex function cdotc(n, cx, incx, cy, incy)
CDOTC
Definition cdotc.f:83
subroutine chpmv(uplo, n, alpha, ap, x, incx, beta, y, incy)
CHPMV
Definition chpmv.f:149
subroutine chpr2(uplo, n, alpha, x, incx, y, incy, ap)
CHPR2
Definition chpr2.f:145
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine csscal(n, sa, cx, incx)
CSSCAL
Definition csscal.f:78
subroutine ctpmv(uplo, trans, diag, n, ap, x, incx)
CTPMV
Definition ctpmv.f:142
subroutine ctpsv(uplo, trans, diag, n, ap, x, incx)
CTPSV
Definition ctpsv.f:144
Here is the call graph for this function:
Here is the caller graph for this function: