LAPACK 3.12.0
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 127 of file chegs2.f.

128*
129* -- LAPACK computational routine --
130* -- LAPACK is a software package provided by Univ. of Tennessee, --
131* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
132*
133* .. Scalar Arguments ..
134 CHARACTER UPLO
135 INTEGER INFO, ITYPE, LDA, LDB, N
136* ..
137* .. Array Arguments ..
138 COMPLEX A( LDA, * ), B( LDB, * )
139* ..
140*
141* =====================================================================
142*
143* .. Parameters ..
144 REAL ONE, HALF
145 parameter( one = 1.0e+0, half = 0.5e+0 )
146 COMPLEX CONE
147 parameter( cone = ( 1.0e+0, 0.0e+0 ) )
148* ..
149* .. Local Scalars ..
150 LOGICAL UPPER
151 INTEGER K
152 REAL AKK, BKK
153 COMPLEX CT
154* ..
155* .. External Subroutines ..
156 EXTERNAL caxpy, cher2, clacgv, csscal, ctrmv, ctrsv,
157 $ xerbla
158* ..
159* .. Intrinsic Functions ..
160 INTRINSIC max
161* ..
162* .. External Functions ..
163 LOGICAL LSAME
164 EXTERNAL lsame
165* ..
166* .. Executable Statements ..
167*
168* Test the input parameters.
169*
170 info = 0
171 upper = lsame( uplo, 'U' )
172 IF( itype.LT.1 .OR. itype.GT.3 ) THEN
173 info = -1
174 ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
175 info = -2
176 ELSE IF( n.LT.0 ) THEN
177 info = -3
178 ELSE IF( lda.LT.max( 1, n ) ) THEN
179 info = -5
180 ELSE IF( ldb.LT.max( 1, n ) ) THEN
181 info = -7
182 END IF
183 IF( info.NE.0 ) THEN
184 CALL xerbla( 'CHEGS2', -info )
185 RETURN
186 END IF
187*
188 IF( itype.EQ.1 ) THEN
189 IF( upper ) THEN
190*
191* Compute inv(U**H)*A*inv(U)
192*
193 DO 10 k = 1, n
194*
195* Update the upper triangle of A(k:n,k:n)
196*
197 akk = real( a( k, k ) )
198 bkk = real( b( k, k ) )
199 akk = akk / bkk**2
200 a( k, k ) = akk
201 IF( k.LT.n ) THEN
202 CALL csscal( n-k, one / bkk, a( k, k+1 ), lda )
203 ct = -half*akk
204 CALL clacgv( n-k, a( k, k+1 ), lda )
205 CALL clacgv( n-k, b( k, k+1 ), ldb )
206 CALL caxpy( n-k, ct, b( k, k+1 ), ldb, a( k, k+1 ),
207 $ lda )
208 CALL cher2( uplo, n-k, -cone, a( k, k+1 ), lda,
209 $ b( k, k+1 ), ldb, a( k+1, k+1 ), lda )
210 CALL caxpy( n-k, ct, b( k, k+1 ), ldb, a( k, k+1 ),
211 $ lda )
212 CALL clacgv( n-k, b( k, k+1 ), ldb )
213 CALL ctrsv( uplo, 'Conjugate transpose', '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 ), 1 )
235 CALL cher2( uplo, n-k, -cone, a( k+1, k ), 1,
236 $ b( k+1, k ), 1, a( k+1, k+1 ), lda )
237 CALL caxpy( n-k, ct, b( k+1, k ), 1, a( k+1, k ), 1 )
238 CALL ctrsv( uplo, 'No transpose', 'Non-unit', n-k,
239 $ b( k+1, k+1 ), ldb, a( k+1, k ), 1 )
240 END IF
241 20 CONTINUE
242 END IF
243 ELSE
244 IF( upper ) THEN
245*
246* Compute U*A*U**H
247*
248 DO 30 k = 1, n
249*
250* Update the upper triangle of A(1:k,1:k)
251*
252 akk = real( a( k, k ) )
253 bkk = real( b( k, k ) )
254 CALL ctrmv( uplo, 'No transpose', 'Non-unit', k-1, b,
255 $ ldb, a( 1, k ), 1 )
256 ct = half*akk
257 CALL caxpy( k-1, ct, b( 1, k ), 1, a( 1, k ), 1 )
258 CALL cher2( uplo, k-1, cone, a( 1, k ), 1, b( 1, k ), 1,
259 $ a, lda )
260 CALL caxpy( k-1, ct, b( 1, k ), 1, a( 1, k ), 1 )
261 CALL csscal( k-1, bkk, a( 1, k ), 1 )
262 a( k, k ) = akk*bkk**2
263 30 CONTINUE
264 ELSE
265*
266* Compute L**H *A*L
267*
268 DO 40 k = 1, n
269*
270* Update the lower triangle of A(1:k,1:k)
271*
272 akk = real( a( k, k ) )
273 bkk = real( b( k, k ) )
274 CALL clacgv( k-1, a( k, 1 ), lda )
275 CALL ctrmv( uplo, 'Conjugate transpose', 'Non-unit', k-1,
276 $ b, ldb, a( k, 1 ), lda )
277 ct = half*akk
278 CALL clacgv( k-1, b( k, 1 ), ldb )
279 CALL caxpy( k-1, ct, b( k, 1 ), ldb, a( k, 1 ), lda )
280 CALL cher2( uplo, k-1, cone, a( k, 1 ), lda, b( k, 1 ),
281 $ ldb, a, lda )
282 CALL caxpy( k-1, ct, b( k, 1 ), ldb, a( k, 1 ), lda )
283 CALL clacgv( k-1, b( k, 1 ), ldb )
284 CALL csscal( k-1, bkk, a( k, 1 ), lda )
285 CALL clacgv( k-1, a( k, 1 ), lda )
286 a( k, k ) = akk*bkk**2
287 40 CONTINUE
288 END IF
289 END IF
290 RETURN
291*
292* End of CHEGS2
293*
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:74
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: