LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine chegst ( integer  ITYPE,
character  UPLO,
integer  N,
complex, dimension( lda, * )  A,
integer  LDA,
complex, dimension( ldb, * )  B,
integer  LDB,
integer  INFO 
)

CHEGST

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

Purpose:
 CHEGST 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 CPOTRF.
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]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.
[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.
Date
September 2012

Definition at line 129 of file chegst.f.

129 *
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..--
133 * September 2012
134 *
135 * .. Scalar Arguments ..
136  CHARACTER uplo
137  INTEGER info, itype, lda, ldb, n
138 * ..
139 * .. Array Arguments ..
140  COMPLEX a( lda, * ), b( ldb, * )
141 * ..
142 *
143 * =====================================================================
144 *
145 * .. Parameters ..
146  REAL one
147  parameter ( one = 1.0e+0 )
148  COMPLEX cone, half
149  parameter ( cone = ( 1.0e+0, 0.0e+0 ),
150  $ half = ( 0.5e+0, 0.0e+0 ) )
151 * ..
152 * .. Local Scalars ..
153  LOGICAL upper
154  INTEGER k, kb, nb
155 * ..
156 * .. External Subroutines ..
157  EXTERNAL chegs2, chemm, cher2k, ctrmm, ctrsm, xerbla
158 * ..
159 * .. Intrinsic Functions ..
160  INTRINSIC max, min
161 * ..
162 * .. External Functions ..
163  LOGICAL lsame
164  INTEGER ilaenv
165  EXTERNAL lsame, ilaenv
166 * ..
167 * .. Executable Statements ..
168 *
169 * Test the input parameters.
170 *
171  info = 0
172  upper = lsame( uplo, 'U' )
173  IF( itype.LT.1 .OR. itype.GT.3 ) THEN
174  info = -1
175  ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
176  info = -2
177  ELSE IF( n.LT.0 ) THEN
178  info = -3
179  ELSE IF( lda.LT.max( 1, n ) ) THEN
180  info = -5
181  ELSE IF( ldb.LT.max( 1, n ) ) THEN
182  info = -7
183  END IF
184  IF( info.NE.0 ) THEN
185  CALL xerbla( 'CHEGST', -info )
186  RETURN
187  END IF
188 *
189 * Quick return if possible
190 *
191  IF( n.EQ.0 )
192  $ RETURN
193 *
194 * Determine the block size for this environment.
195 *
196  nb = ilaenv( 1, 'CHEGST', uplo, n, -1, -1, -1 )
197 *
198  IF( nb.LE.1 .OR. nb.GE.n ) THEN
199 *
200 * Use unblocked code
201 *
202  CALL chegs2( itype, uplo, n, a, lda, b, ldb, info )
203  ELSE
204 *
205 * Use blocked code
206 *
207  IF( itype.EQ.1 ) THEN
208  IF( upper ) THEN
209 *
210 * Compute inv(U**H)*A*inv(U)
211 *
212  DO 10 k = 1, n, nb
213  kb = min( n-k+1, nb )
214 *
215 * Update the upper triangle of A(k:n,k:n)
216 *
217  CALL chegs2( itype, uplo, kb, a( k, k ), lda,
218  $ b( k, k ), ldb, info )
219  IF( k+kb.LE.n ) THEN
220  CALL ctrsm( 'Left', uplo, 'Conjugate transpose',
221  $ 'Non-unit', kb, n-k-kb+1, cone,
222  $ b( k, k ), ldb, a( k, k+kb ), lda )
223  CALL chemm( 'Left', uplo, kb, n-k-kb+1, -half,
224  $ a( k, k ), lda, b( k, k+kb ), ldb,
225  $ cone, a( k, k+kb ), lda )
226  CALL cher2k( uplo, 'Conjugate transpose', n-k-kb+1,
227  $ kb, -cone, a( k, k+kb ), lda,
228  $ b( k, k+kb ), ldb, one,
229  $ a( k+kb, k+kb ), lda )
230  CALL chemm( 'Left', uplo, kb, n-k-kb+1, -half,
231  $ a( k, k ), lda, b( k, k+kb ), ldb,
232  $ cone, a( k, k+kb ), lda )
233  CALL ctrsm( 'Right', uplo, 'No transpose',
234  $ 'Non-unit', kb, n-k-kb+1, cone,
235  $ b( k+kb, k+kb ), ldb, a( k, k+kb ),
236  $ lda )
237  END IF
238  10 CONTINUE
239  ELSE
240 *
241 * Compute inv(L)*A*inv(L**H)
242 *
243  DO 20 k = 1, n, nb
244  kb = min( n-k+1, nb )
245 *
246 * Update the lower triangle of A(k:n,k:n)
247 *
248  CALL chegs2( itype, uplo, kb, a( k, k ), lda,
249  $ b( k, k ), ldb, info )
250  IF( k+kb.LE.n ) THEN
251  CALL ctrsm( 'Right', uplo, 'Conjugate transpose',
252  $ 'Non-unit', n-k-kb+1, kb, cone,
253  $ b( k, k ), ldb, a( k+kb, k ), lda )
254  CALL chemm( 'Right', uplo, n-k-kb+1, kb, -half,
255  $ a( k, k ), lda, b( k+kb, k ), ldb,
256  $ cone, a( k+kb, k ), lda )
257  CALL cher2k( uplo, 'No transpose', n-k-kb+1, kb,
258  $ -cone, a( k+kb, k ), lda,
259  $ b( k+kb, k ), ldb, one,
260  $ a( k+kb, k+kb ), lda )
261  CALL chemm( 'Right', uplo, n-k-kb+1, kb, -half,
262  $ a( k, k ), lda, b( k+kb, k ), ldb,
263  $ cone, a( k+kb, k ), lda )
264  CALL ctrsm( 'Left', uplo, 'No transpose',
265  $ 'Non-unit', n-k-kb+1, kb, cone,
266  $ b( k+kb, k+kb ), ldb, a( k+kb, k ),
267  $ lda )
268  END IF
269  20 CONTINUE
270  END IF
271  ELSE
272  IF( upper ) THEN
273 *
274 * Compute U*A*U**H
275 *
276  DO 30 k = 1, n, nb
277  kb = min( n-k+1, nb )
278 *
279 * Update the upper triangle of A(1:k+kb-1,1:k+kb-1)
280 *
281  CALL ctrmm( 'Left', uplo, 'No transpose', 'Non-unit',
282  $ k-1, kb, cone, b, ldb, a( 1, k ), lda )
283  CALL chemm( 'Right', uplo, k-1, kb, half, a( k, k ),
284  $ lda, b( 1, k ), ldb, cone, a( 1, k ),
285  $ lda )
286  CALL cher2k( uplo, 'No transpose', k-1, kb, cone,
287  $ a( 1, k ), lda, b( 1, k ), ldb, one, a,
288  $ lda )
289  CALL chemm( 'Right', uplo, k-1, kb, half, a( k, k ),
290  $ lda, b( 1, k ), ldb, cone, a( 1, k ),
291  $ lda )
292  CALL ctrmm( 'Right', uplo, 'Conjugate transpose',
293  $ 'Non-unit', k-1, kb, cone, b( k, k ), ldb,
294  $ a( 1, k ), lda )
295  CALL chegs2( itype, uplo, kb, a( k, k ), lda,
296  $ b( k, k ), ldb, info )
297  30 CONTINUE
298  ELSE
299 *
300 * Compute L**H*A*L
301 *
302  DO 40 k = 1, n, nb
303  kb = min( n-k+1, nb )
304 *
305 * Update the lower triangle of A(1:k+kb-1,1:k+kb-1)
306 *
307  CALL ctrmm( 'Right', uplo, 'No transpose', 'Non-unit',
308  $ kb, k-1, cone, b, ldb, a( k, 1 ), lda )
309  CALL chemm( 'Left', uplo, kb, k-1, half, a( k, k ),
310  $ lda, b( k, 1 ), ldb, cone, a( k, 1 ),
311  $ lda )
312  CALL cher2k( uplo, 'Conjugate transpose', k-1, kb,
313  $ cone, a( k, 1 ), lda, b( k, 1 ), ldb,
314  $ one, a, lda )
315  CALL chemm( 'Left', uplo, kb, k-1, half, a( k, k ),
316  $ lda, b( k, 1 ), ldb, cone, a( k, 1 ),
317  $ lda )
318  CALL ctrmm( 'Left', uplo, 'Conjugate transpose',
319  $ 'Non-unit', kb, k-1, cone, b( k, k ), ldb,
320  $ a( k, 1 ), lda )
321  CALL chegs2( itype, uplo, kb, a( k, k ), lda,
322  $ b( k, k ), ldb, info )
323  40 CONTINUE
324  END IF
325  END IF
326  END IF
327  RETURN
328 *
329 * End of CHEGST
330 *
subroutine chemm(SIDE, UPLO, M, N, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
CHEMM
Definition: chemm.f:193
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine ctrsm(SIDE, UPLO, TRANSA, DIAG, M, N, ALPHA, A, LDA, B, LDB)
CTRSM
Definition: ctrsm.f:182
subroutine chegs2(ITYPE, UPLO, N, A, LDA, B, LDB, INFO)
CHEGS2 reduces a Hermitian definite generalized eigenproblem to standard form, using the factorizatio...
Definition: chegs2.f:129
subroutine cher2k(UPLO, TRANS, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
CHER2K
Definition: cher2k.f:199
integer function ilaenv(ISPEC, NAME, OPTS, N1, N2, N3, N4)
Definition: tstiee.f:83
subroutine ctrmm(SIDE, UPLO, TRANSA, DIAG, M, N, ALPHA, A, LDA, B, LDB)
CTRMM
Definition: ctrmm.f:179
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: