LAPACK  3.9.0
LAPACK: Linear Algebra PACKage
chegst.f
Go to the documentation of this file.
1 *> \brief \b CHEGST
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download CHEGST + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/chegst.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/chegst.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/chegst.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE CHEGST( ITYPE, UPLO, N, A, LDA, B, LDB, INFO )
22 *
23 * .. Scalar Arguments ..
24 * CHARACTER UPLO
25 * INTEGER INFO, ITYPE, LDA, LDB, N
26 * ..
27 * .. Array Arguments ..
28 * COMPLEX A( LDA, * ), B( LDB, * )
29 * ..
30 *
31 *
32 *> \par Purpose:
33 * =============
34 *>
35 *> \verbatim
36 *>
37 *> CHEGST reduces a complex Hermitian-definite generalized
38 *> eigenproblem to standard form.
39 *>
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)
42 *>
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.
45 *>
46 *> B must have been previously factorized as U**H*U or L*L**H by CPOTRF.
47 *> \endverbatim
48 *
49 * Arguments:
50 * ==========
51 *
52 *> \param[in] ITYPE
53 *> \verbatim
54 *> ITYPE is INTEGER
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.
57 *> \endverbatim
58 *>
59 *> \param[in] UPLO
60 *> \verbatim
61 *> UPLO is CHARACTER*1
62 *> = 'U': Upper triangle of A is stored and B is factored as
63 *> U**H*U;
64 *> = 'L': Lower triangle of A is stored and B is factored as
65 *> L*L**H.
66 *> \endverbatim
67 *>
68 *> \param[in] N
69 *> \verbatim
70 *> N is INTEGER
71 *> The order of the matrices A and B. N >= 0.
72 *> \endverbatim
73 *>
74 *> \param[in,out] A
75 *> \verbatim
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.
84 *>
85 *> On exit, if INFO = 0, the transformed matrix, stored in the
86 *> same format as A.
87 *> \endverbatim
88 *>
89 *> \param[in] LDA
90 *> \verbatim
91 *> LDA is INTEGER
92 *> The leading dimension of the array A. LDA >= max(1,N).
93 *> \endverbatim
94 *>
95 *> \param[in,out] B
96 *> \verbatim
97 *> B is COMPLEX array, dimension (LDB,N)
98 *> The triangular factor from the Cholesky factorization of B,
99 *> as returned by CPOTRF.
100 *> B is modified by the routine but restored on exit.
101 *> \endverbatim
102 *>
103 *> \param[in] LDB
104 *> \verbatim
105 *> LDB is INTEGER
106 *> The leading dimension of the array B. LDB >= max(1,N).
107 *> \endverbatim
108 *>
109 *> \param[out] INFO
110 *> \verbatim
111 *> INFO is INTEGER
112 *> = 0: successful exit
113 *> < 0: if INFO = -i, the i-th argument had an illegal value
114 *> \endverbatim
115 *
116 * Authors:
117 * ========
118 *
119 *> \author Univ. of Tennessee
120 *> \author Univ. of California Berkeley
121 *> \author Univ. of Colorado Denver
122 *> \author NAG Ltd.
123 *
124 *> \date December 2016
125 *
126 *> \ingroup complexHEcomputational
127 *
128 * =====================================================================
129  SUBROUTINE chegst( ITYPE, UPLO, N, A, LDA, B, LDB, INFO )
130 *
131 * -- LAPACK computational routine (version 3.7.0) --
132 * -- LAPACK is a software package provided by Univ. of Tennessee, --
133 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
134 * December 2016
135 *
136 * .. Scalar Arguments ..
137  CHARACTER UPLO
138  INTEGER INFO, ITYPE, LDA, LDB, N
139 * ..
140 * .. Array Arguments ..
141  COMPLEX A( LDA, * ), B( LDB, * )
142 * ..
143 *
144 * =====================================================================
145 *
146 * .. Parameters ..
147  REAL ONE
148  parameter( one = 1.0e+0 )
149  COMPLEX CONE, HALF
150  parameter( cone = ( 1.0e+0, 0.0e+0 ),
151  $ half = ( 0.5e+0, 0.0e+0 ) )
152 * ..
153 * .. Local Scalars ..
154  LOGICAL UPPER
155  INTEGER K, KB, NB
156 * ..
157 * .. External Subroutines ..
158  EXTERNAL chegs2, chemm, cher2k, ctrmm, ctrsm, xerbla
159 * ..
160 * .. Intrinsic Functions ..
161  INTRINSIC max, min
162 * ..
163 * .. External Functions ..
164  LOGICAL LSAME
165  INTEGER ILAENV
166  EXTERNAL lsame, ilaenv
167 * ..
168 * .. Executable Statements ..
169 *
170 * Test the input parameters.
171 *
172  info = 0
173  upper = lsame( uplo, 'U' )
174  IF( itype.LT.1 .OR. itype.GT.3 ) THEN
175  info = -1
176  ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
177  info = -2
178  ELSE IF( n.LT.0 ) THEN
179  info = -3
180  ELSE IF( lda.LT.max( 1, n ) ) THEN
181  info = -5
182  ELSE IF( ldb.LT.max( 1, n ) ) THEN
183  info = -7
184  END IF
185  IF( info.NE.0 ) THEN
186  CALL xerbla( 'CHEGST', -info )
187  RETURN
188  END IF
189 *
190 * Quick return if possible
191 *
192  IF( n.EQ.0 )
193  $ RETURN
194 *
195 * Determine the block size for this environment.
196 *
197  nb = ilaenv( 1, 'CHEGST', uplo, n, -1, -1, -1 )
198 *
199  IF( nb.LE.1 .OR. nb.GE.n ) THEN
200 *
201 * Use unblocked code
202 *
203  CALL chegs2( itype, uplo, n, a, lda, b, ldb, info )
204  ELSE
205 *
206 * Use blocked code
207 *
208  IF( itype.EQ.1 ) THEN
209  IF( upper ) THEN
210 *
211 * Compute inv(U**H)*A*inv(U)
212 *
213  DO 10 k = 1, n, nb
214  kb = min( n-k+1, nb )
215 *
216 * Update the upper triangle of A(k:n,k:n)
217 *
218  CALL chegs2( itype, uplo, kb, a( k, k ), lda,
219  $ b( k, k ), ldb, info )
220  IF( k+kb.LE.n ) THEN
221  CALL ctrsm( 'Left', uplo, 'Conjugate transpose',
222  $ 'Non-unit', kb, n-k-kb+1, cone,
223  $ b( k, k ), ldb, a( k, k+kb ), lda )
224  CALL chemm( 'Left', uplo, kb, n-k-kb+1, -half,
225  $ a( k, k ), lda, b( k, k+kb ), ldb,
226  $ cone, a( k, k+kb ), lda )
227  CALL cher2k( uplo, 'Conjugate transpose', n-k-kb+1,
228  $ kb, -cone, a( k, k+kb ), lda,
229  $ b( k, k+kb ), ldb, one,
230  $ a( k+kb, k+kb ), lda )
231  CALL chemm( 'Left', uplo, kb, n-k-kb+1, -half,
232  $ a( k, k ), lda, b( k, k+kb ), ldb,
233  $ cone, a( k, k+kb ), lda )
234  CALL ctrsm( 'Right', uplo, 'No transpose',
235  $ 'Non-unit', kb, n-k-kb+1, cone,
236  $ b( k+kb, k+kb ), ldb, a( k, k+kb ),
237  $ lda )
238  END IF
239  10 CONTINUE
240  ELSE
241 *
242 * Compute inv(L)*A*inv(L**H)
243 *
244  DO 20 k = 1, n, nb
245  kb = min( n-k+1, nb )
246 *
247 * Update the lower triangle of A(k:n,k:n)
248 *
249  CALL chegs2( itype, uplo, kb, a( k, k ), lda,
250  $ b( k, k ), ldb, info )
251  IF( k+kb.LE.n ) THEN
252  CALL ctrsm( 'Right', uplo, 'Conjugate transpose',
253  $ 'Non-unit', n-k-kb+1, kb, cone,
254  $ b( k, k ), ldb, a( k+kb, k ), lda )
255  CALL chemm( 'Right', uplo, n-k-kb+1, kb, -half,
256  $ a( k, k ), lda, b( k+kb, k ), ldb,
257  $ cone, a( k+kb, k ), lda )
258  CALL cher2k( uplo, 'No transpose', n-k-kb+1, kb,
259  $ -cone, a( k+kb, k ), lda,
260  $ b( k+kb, k ), ldb, one,
261  $ a( k+kb, k+kb ), lda )
262  CALL chemm( 'Right', uplo, n-k-kb+1, kb, -half,
263  $ a( k, k ), lda, b( k+kb, k ), ldb,
264  $ cone, a( k+kb, k ), lda )
265  CALL ctrsm( 'Left', uplo, 'No transpose',
266  $ 'Non-unit', n-k-kb+1, kb, cone,
267  $ b( k+kb, k+kb ), ldb, a( k+kb, k ),
268  $ lda )
269  END IF
270  20 CONTINUE
271  END IF
272  ELSE
273  IF( upper ) THEN
274 *
275 * Compute U*A*U**H
276 *
277  DO 30 k = 1, n, nb
278  kb = min( n-k+1, nb )
279 *
280 * Update the upper triangle of A(1:k+kb-1,1:k+kb-1)
281 *
282  CALL ctrmm( 'Left', uplo, 'No transpose', 'Non-unit',
283  $ k-1, kb, cone, b, ldb, a( 1, k ), lda )
284  CALL chemm( 'Right', uplo, k-1, kb, half, a( k, k ),
285  $ lda, b( 1, k ), ldb, cone, a( 1, k ),
286  $ lda )
287  CALL cher2k( uplo, 'No transpose', k-1, kb, cone,
288  $ a( 1, k ), lda, b( 1, k ), ldb, one, a,
289  $ lda )
290  CALL chemm( 'Right', uplo, k-1, kb, half, a( k, k ),
291  $ lda, b( 1, k ), ldb, cone, a( 1, k ),
292  $ lda )
293  CALL ctrmm( 'Right', uplo, 'Conjugate transpose',
294  $ 'Non-unit', k-1, kb, cone, b( k, k ), ldb,
295  $ a( 1, k ), lda )
296  CALL chegs2( itype, uplo, kb, a( k, k ), lda,
297  $ b( k, k ), ldb, info )
298  30 CONTINUE
299  ELSE
300 *
301 * Compute L**H*A*L
302 *
303  DO 40 k = 1, n, nb
304  kb = min( n-k+1, nb )
305 *
306 * Update the lower triangle of A(1:k+kb-1,1:k+kb-1)
307 *
308  CALL ctrmm( 'Right', uplo, 'No transpose', 'Non-unit',
309  $ kb, k-1, cone, b, ldb, a( k, 1 ), lda )
310  CALL chemm( 'Left', uplo, kb, k-1, half, a( k, k ),
311  $ lda, b( k, 1 ), ldb, cone, a( k, 1 ),
312  $ lda )
313  CALL cher2k( uplo, 'Conjugate transpose', k-1, kb,
314  $ cone, a( k, 1 ), lda, b( k, 1 ), ldb,
315  $ one, a, lda )
316  CALL chemm( 'Left', uplo, kb, k-1, half, a( k, k ),
317  $ lda, b( k, 1 ), ldb, cone, a( k, 1 ),
318  $ lda )
319  CALL ctrmm( 'Left', uplo, 'Conjugate transpose',
320  $ 'Non-unit', kb, k-1, cone, b( k, k ), ldb,
321  $ a( k, 1 ), lda )
322  CALL chegs2( itype, uplo, kb, a( k, k ), lda,
323  $ b( k, k ), ldb, info )
324  40 CONTINUE
325  END IF
326  END IF
327  END IF
328  RETURN
329 *
330 * End of CHEGST
331 *
332  END
chegs2
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:130
chemm
subroutine chemm(SIDE, UPLO, M, N, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
CHEMM
Definition: chemm.f:193
ctrsm
subroutine ctrsm(SIDE, UPLO, TRANSA, DIAG, M, N, ALPHA, A, LDA, B, LDB)
CTRSM
Definition: ctrsm.f:182
chegst
subroutine chegst(ITYPE, UPLO, N, A, LDA, B, LDB, INFO)
CHEGST
Definition: chegst.f:130
cher2k
subroutine cher2k(UPLO, TRANS, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
CHER2K
Definition: cher2k.f:199
xerbla
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
ctrmm
subroutine ctrmm(SIDE, UPLO, TRANSA, DIAG, M, N, ALPHA, A, LDA, B, LDB)
CTRMM
Definition: ctrmm.f:179