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

◆ chegs2()

subroutine chegs2 ( integer itype,
character uplo,
integer n,
complex, dimension( lda, * ) a,
integer lda,
complex, dimension( ldb, * ) b,
integer ldb,
integer info )

CHEGS2 reduces a Hermitian definite generalized eigenproblem to standard form, using the factorization results obtained from cpotrf (unblocked algorithm).

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

Purpose:
!>
!> CHEGS2 reduces a complex Hermitian-definite generalized
!> eigenproblem to standard form.
!>
!> 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 ZPOTRF.
!> 
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
!>          Specifies whether the upper or lower triangular part of the
!>          Hermitian matrix A is stored, and how B has been factorized.
!>          = 'U':  Upper triangular
!>          = 'L':  Lower triangular
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrices A and B.  N >= 0.
!> 
[in,out]A
!>          A is COMPLEX array, dimension (LDA,N)
!>          On entry, the Hermitian matrix A.  If UPLO = 'U', the leading
!>          n by n upper triangular part of A contains the upper
!>          triangular part of the matrix A, and the strictly lower
!>          triangular part of A is not referenced.  If UPLO = 'L', the
!>          leading n by n lower triangular part of A contains the lower
!>          triangular part of the matrix A, and the strictly upper
!>          triangular part of A is not referenced.
!>
!>          On exit, if INFO = 0, the transformed matrix, stored in the
!>          same format as A.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the array A.  LDA >= max(1,N).
!> 
[in,out]B
!>          B is COMPLEX array, dimension (LDB,N)
!>          The triangular factor from the Cholesky factorization of B,
!>          as returned by CPOTRF.
!>          B is modified by the routine but restored on exit.
!> 
[in]LDB
!>          LDB is INTEGER
!>          The leading dimension of the array B.  LDB >= max(1,N).
!> 
[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 125 of file chegs2.f.

126*
127* -- LAPACK computational routine --
128* -- LAPACK is a software package provided by Univ. of Tennessee, --
129* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
130*
131* .. Scalar Arguments ..
132 CHARACTER UPLO
133 INTEGER INFO, ITYPE, LDA, LDB, N
134* ..
135* .. Array Arguments ..
136 COMPLEX A( LDA, * ), B( LDB, * )
137* ..
138*
139* =====================================================================
140*
141* .. Parameters ..
142 REAL ONE, HALF
143 parameter( one = 1.0e+0, half = 0.5e+0 )
144 COMPLEX CONE
145 parameter( cone = ( 1.0e+0, 0.0e+0 ) )
146* ..
147* .. Local Scalars ..
148 LOGICAL UPPER
149 INTEGER K
150 REAL AKK, BKK
151 COMPLEX CT
152* ..
153* .. External Subroutines ..
154 EXTERNAL caxpy, cher2, clacgv, csscal, ctrmv,
155 $ ctrsv,
156 $ xerbla
157* ..
158* .. Intrinsic Functions ..
159 INTRINSIC max
160* ..
161* .. External Functions ..
162 LOGICAL LSAME
163 EXTERNAL lsame
164* ..
165* .. Executable Statements ..
166*
167* Test the input parameters.
168*
169 info = 0
170 upper = lsame( uplo, 'U' )
171 IF( itype.LT.1 .OR. itype.GT.3 ) THEN
172 info = -1
173 ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
174 info = -2
175 ELSE IF( n.LT.0 ) THEN
176 info = -3
177 ELSE IF( lda.LT.max( 1, n ) ) THEN
178 info = -5
179 ELSE IF( ldb.LT.max( 1, n ) ) THEN
180 info = -7
181 END IF
182 IF( info.NE.0 ) THEN
183 CALL xerbla( 'CHEGS2', -info )
184 RETURN
185 END IF
186*
187 IF( itype.EQ.1 ) THEN
188 IF( upper ) THEN
189*
190* Compute inv(U**H)*A*inv(U)
191*
192 DO 10 k = 1, n
193*
194* Update the upper triangle of A(k:n,k:n)
195*
196 akk = real( a( k, k ) )
197 bkk = real( b( k, k ) )
198 akk = akk / bkk**2
199 a( k, k ) = akk
200 IF( k.LT.n ) THEN
201 CALL csscal( n-k, one / bkk, a( k, k+1 ), lda )
202 ct = -half*akk
203 CALL clacgv( n-k, a( k, k+1 ), lda )
204 CALL clacgv( n-k, b( k, k+1 ), ldb )
205 CALL caxpy( n-k, ct, b( k, k+1 ), ldb, a( k, k+1 ),
206 $ lda )
207 CALL cher2( uplo, n-k, -cone, a( k, k+1 ), lda,
208 $ b( k, k+1 ), ldb, a( k+1, k+1 ), lda )
209 CALL caxpy( n-k, ct, b( k, k+1 ), ldb, a( k, k+1 ),
210 $ lda )
211 CALL clacgv( n-k, b( k, k+1 ), ldb )
212 CALL ctrsv( uplo, 'Conjugate transpose',
213 $ 'Non-unit',
214 $ n-k, b( k+1, k+1 ), ldb, a( k, k+1 ),
215 $ lda )
216 CALL clacgv( n-k, a( k, k+1 ), lda )
217 END IF
218 10 CONTINUE
219 ELSE
220*
221* Compute inv(L)*A*inv(L**H)
222*
223 DO 20 k = 1, n
224*
225* Update the lower triangle of A(k:n,k:n)
226*
227 akk = real( a( k, k ) )
228 bkk = real( b( k, k ) )
229 akk = akk / bkk**2
230 a( k, k ) = akk
231 IF( k.LT.n ) THEN
232 CALL csscal( n-k, one / bkk, a( k+1, k ), 1 )
233 ct = -half*akk
234 CALL caxpy( n-k, ct, b( k+1, k ), 1, a( k+1, k ),
235 $ 1 )
236 CALL cher2( uplo, n-k, -cone, a( k+1, k ), 1,
237 $ b( k+1, k ), 1, a( k+1, k+1 ), lda )
238 CALL caxpy( n-k, ct, b( k+1, k ), 1, a( k+1, k ),
239 $ 1 )
240 CALL ctrsv( uplo, 'No transpose', 'Non-unit', n-k,
241 $ b( k+1, k+1 ), ldb, a( k+1, k ), 1 )
242 END IF
243 20 CONTINUE
244 END IF
245 ELSE
246 IF( upper ) THEN
247*
248* Compute U*A*U**H
249*
250 DO 30 k = 1, n
251*
252* Update the upper triangle of A(1:k,1:k)
253*
254 akk = real( a( k, k ) )
255 bkk = real( b( k, k ) )
256 CALL ctrmv( uplo, 'No transpose', 'Non-unit', k-1, b,
257 $ ldb, a( 1, k ), 1 )
258 ct = half*akk
259 CALL caxpy( k-1, ct, b( 1, k ), 1, a( 1, k ), 1 )
260 CALL cher2( uplo, k-1, cone, a( 1, k ), 1, b( 1, k ),
261 $ 1,
262 $ a, lda )
263 CALL caxpy( k-1, ct, b( 1, k ), 1, a( 1, k ), 1 )
264 CALL csscal( k-1, bkk, a( 1, k ), 1 )
265 a( k, k ) = akk*bkk**2
266 30 CONTINUE
267 ELSE
268*
269* Compute L**H *A*L
270*
271 DO 40 k = 1, n
272*
273* Update the lower triangle of A(1:k,1:k)
274*
275 akk = real( a( k, k ) )
276 bkk = real( b( k, k ) )
277 CALL clacgv( k-1, a( k, 1 ), lda )
278 CALL ctrmv( uplo, 'Conjugate transpose', 'Non-unit',
279 $ k-1,
280 $ b, ldb, a( k, 1 ), lda )
281 ct = half*akk
282 CALL clacgv( k-1, b( k, 1 ), ldb )
283 CALL caxpy( k-1, ct, b( k, 1 ), ldb, a( k, 1 ), lda )
284 CALL cher2( uplo, k-1, cone, a( k, 1 ), lda, b( k,
285 $ 1 ),
286 $ ldb, a, lda )
287 CALL caxpy( k-1, ct, b( k, 1 ), ldb, a( k, 1 ), lda )
288 CALL clacgv( k-1, b( k, 1 ), ldb )
289 CALL csscal( k-1, bkk, a( k, 1 ), lda )
290 CALL clacgv( k-1, a( k, 1 ), lda )
291 a( k, k ) = akk*bkk**2
292 40 CONTINUE
293 END IF
294 END IF
295 RETURN
296*
297* End of CHEGS2
298*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine caxpy(n, ca, cx, incx, cy, incy)
CAXPY
Definition caxpy.f:88
subroutine cher2(uplo, n, alpha, x, incx, y, incy, a, lda)
CHER2
Definition cher2.f:150
subroutine clacgv(n, x, incx)
CLACGV conjugates a complex vector.
Definition clacgv.f:72
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine csscal(n, sa, cx, incx)
CSSCAL
Definition csscal.f:78
subroutine ctrmv(uplo, trans, diag, n, a, lda, x, incx)
CTRMV
Definition ctrmv.f:147
subroutine ctrsv(uplo, trans, diag, n, a, lda, x, incx)
CTRSV
Definition ctrsv.f:149
Here is the call graph for this function:
Here is the caller graph for this function: