1 *> \brief \b CHEGS2 reduces a Hermitian definite generalized eigenproblem to standard form, using the factorization results obtained from cpotrf (unblocked algorithm).
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CHEGS2 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/chegs2.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/chegs2.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/chegs2.f">
21 * SUBROUTINE CHEGS2( ITYPE, UPLO, N, A, LDA, B, LDB, INFO )
23 * .. Scalar Arguments ..
25 * INTEGER INFO, ITYPE, LDA, LDB, N
27 * .. Array Arguments ..
28 * COMPLEX A( LDA, * ), B( LDB, * )
37 *> CHEGS2 reduces a complex Hermitian-definite generalized
38 *> eigenproblem to standard form.
40 *> If ITYPE = 1, the problem is A*x = lambda*B*x,
41 *> and A is overwritten by inv(U**H)*A*inv(U) or inv(L)*A*inv(L**H)
43 *> If ITYPE = 2 or 3, the problem is A*B*x = lambda*x or
44 *> B*A*x = lambda*x, and A is overwritten by U*A*U**H or L**H *A*L.
46 *> B must have been previously factorized as U**H *U or L*L**H by ZPOTRF.
55 *> = 1: compute inv(U**H)*A*inv(U) or inv(L)*A*inv(L**H);
56 *> = 2 or 3: compute U*A*U**H or L**H *A*L.
61 *> UPLO is CHARACTER*1
62 *> Specifies whether the upper or lower triangular part of the
63 *> Hermitian matrix A is stored, and how B has been factorized.
64 *> = 'U': Upper triangular
65 *> = 'L': Lower triangular
71 *> The order of the matrices A and B. N >= 0.
76 *> A is COMPLEX array, dimension (LDA,N)
77 *> On entry, the Hermitian matrix A. If UPLO = 'U', the leading
78 *> n by n upper triangular part of A contains the upper
79 *> triangular part of the matrix A, and the strictly lower
80 *> triangular part of A is not referenced. If UPLO = 'L', the
81 *> leading n by n lower triangular part of A contains the lower
82 *> triangular part of the matrix A, and the strictly upper
83 *> triangular part of A is not referenced.
85 *> On exit, if INFO = 0, the transformed matrix, stored in the
92 *> The leading dimension of the array A. LDA >= max(1,N).
97 *> B is COMPLEX array, dimension (LDB,N)
98 *> The triangular factor from the Cholesky factorization of B,
99 *> as returned by CPOTRF.
105 *> The leading dimension of the array B. LDB >= max(1,N).
111 *> = 0: successful exit.
112 *> < 0: if INFO = -i, the i-th argument had an illegal value.
118 *> \author Univ. of Tennessee
119 *> \author Univ. of California Berkeley
120 *> \author Univ. of Colorado Denver
123 *> \date September 2012
125 *> \ingroup complexHEcomputational
127 * =====================================================================
128 SUBROUTINE CHEGS2( ITYPE, UPLO, N, A, LDA, B, LDB, INFO )
130 * -- LAPACK computational routine (version 3.4.2) --
131 * -- LAPACK is a software package provided by Univ. of Tennessee, --
132 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
135 * .. Scalar Arguments ..
137 INTEGER INFO, ITYPE, LDA, LDB, N
139 * .. Array Arguments ..
140 COMPLEX A( LDA, * ), B( LDB, * )
143 * =====================================================================
147 PARAMETER ( ONE = 1.0E+0, HALF = 0.5E+0 )
149 PARAMETER ( CONE = ( 1.0E+0, 0.0E+0 ) )
151 * .. Local Scalars ..
157 * .. External Subroutines ..
158 EXTERNAL CAXPY, CHER2, CLACGV, CSSCAL, CTRMV, CTRSV,
161 * .. Intrinsic Functions ..
164 * .. External Functions ..
168 * .. Executable Statements ..
170 * Test the input parameters.
173 UPPER = LSAME( UPLO, 'U' )
174 IF( ITYPE.LT.1 .OR. ITYPE.GT.3 ) THEN
176 ELSE IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
178 ELSE IF( N.LT.0 ) THEN
180 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
182 ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
186 CALL XERBLA( 'CHEGS2', -INFO )
190 IF( ITYPE.EQ.1 ) THEN
193 * Compute inv(U**H)*A*inv(U)
197 * Update the upper triangle of A(k:n,k:n)
204 CALL CSSCAL( N-K, ONE / BKK, A( K, K+1 ), LDA )
206 CALL CLACGV( N-K, A( K, K+1 ), LDA )
207 CALL CLACGV( N-K, B( K, K+1 ), LDB )
208 CALL CAXPY( N-K, CT, B( K, K+1 ), LDB, A( K, K+1 ),
210 CALL CHER2( UPLO, N-K, -CONE, A( K, K+1 ), LDA,
211 $ B( K, K+1 ), LDB, A( K+1, K+1 ), LDA )
212 CALL CAXPY( N-K, CT, B( K, K+1 ), LDB, A( K, K+1 ),
214 CALL CLACGV( N-K, B( K, K+1 ), LDB )
215 CALL CTRSV( UPLO, 'Conjugate transpose', 'Non-unit',
216 $ N-K, B( K+1, K+1 ), LDB, A( K, K+1 ),
218 CALL CLACGV( N-K, A( K, K+1 ), LDA )
223 * Compute inv(L)*A*inv(L**H)
227 * Update the lower triangle of A(k:n,k:n)
234 CALL CSSCAL( N-K, ONE / BKK, A( K+1, K ), 1 )
236 CALL CAXPY( N-K, CT, B( K+1, K ), 1, A( K+1, K ), 1 )
237 CALL CHER2( UPLO, N-K, -CONE, A( K+1, K ), 1,
238 $ B( K+1, K ), 1, A( K+1, K+1 ), LDA )
239 CALL CAXPY( N-K, CT, B( K+1, K ), 1, A( K+1, K ), 1 )
240 CALL CTRSV( UPLO, 'No transpose', 'Non-unit', N-K,
241 $ B( K+1, K+1 ), LDB, A( K+1, K ), 1 )
252 * Update the upper triangle of A(1:k,1:k)
256 CALL CTRMV( UPLO, 'No transpose', 'Non-unit', K-1, B,
257 $ LDB, A( 1, K ), 1 )
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 ), 1,
262 CALL CAXPY( K-1, CT, B( 1, K ), 1, A( 1, K ), 1 )
263 CALL CSSCAL( K-1, BKK, A( 1, K ), 1 )
264 A( K, K ) = AKK*BKK**2
272 * Update the lower triangle of A(1:k,1:k)
276 CALL CLACGV( K-1, A( K, 1 ), LDA )
277 CALL CTRMV( UPLO, 'Conjugate transpose', 'Non-unit', K-1,
278 $ B, LDB, A( K, 1 ), LDA )
280 CALL CLACGV( K-1, B( K, 1 ), LDB )
281 CALL CAXPY( K-1, CT, B( K, 1 ), LDB, A( K, 1 ), LDA )
282 CALL CHER2( UPLO, K-1, CONE, A( K, 1 ), LDA, B( K, 1 ),
284 CALL CAXPY( K-1, CT, B( K, 1 ), LDB, A( K, 1 ), LDA )
285 CALL CLACGV( K-1, B( K, 1 ), LDB )
286 CALL CSSCAL( K-1, BKK, A( K, 1 ), LDA )
287 CALL CLACGV( K-1, A( K, 1 ), LDA )
288 A( K, K ) = AKK*BKK**2