LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dsygst.f
Go to the documentation of this file.
1*> \brief \b DSYGST
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download DSYGST + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dsygst.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dsygst.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dsygst.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE DSYGST( 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* DOUBLE PRECISION A( LDA, * ), B( LDB, * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> DSYGST reduces a real symmetric-definite generalized eigenproblem
38*> to standard form.
39*>
40*> If ITYPE = 1, the problem is A*x = lambda*B*x,
41*> and A is overwritten by inv(U**T)*A*inv(U) or inv(L)*A*inv(L**T)
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**T or L**T*A*L.
45*>
46*> B must have been previously factorized as U**T*U or L*L**T by DPOTRF.
47*> \endverbatim
48*
49* Arguments:
50* ==========
51*
52*> \param[in] ITYPE
53*> \verbatim
54*> ITYPE is INTEGER
55*> = 1: compute inv(U**T)*A*inv(U) or inv(L)*A*inv(L**T);
56*> = 2 or 3: compute U*A*U**T or L**T*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**T*U;
64*> = 'L': Lower triangle of A is stored and B is factored as
65*> L*L**T.
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 DOUBLE PRECISION array, dimension (LDA,N)
77*> On entry, the symmetric 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] B
96*> \verbatim
97*> B is DOUBLE PRECISION array, dimension (LDB,N)
98*> The triangular factor from the Cholesky factorization of B,
99*> as returned by DPOTRF.
100*> \endverbatim
101*>
102*> \param[in] LDB
103*> \verbatim
104*> LDB is INTEGER
105*> The leading dimension of the array B. LDB >= max(1,N).
106*> \endverbatim
107*>
108*> \param[out] INFO
109*> \verbatim
110*> INFO is INTEGER
111*> = 0: successful exit
112*> < 0: if INFO = -i, the i-th argument had an illegal value
113*> \endverbatim
114*
115* Authors:
116* ========
117*
118*> \author Univ. of Tennessee
119*> \author Univ. of California Berkeley
120*> \author Univ. of Colorado Denver
121*> \author NAG Ltd.
122*
123*> \ingroup hegst
124*
125* =====================================================================
126 SUBROUTINE dsygst( ITYPE, UPLO, N, A, LDA, B, LDB, INFO )
127*
128* -- LAPACK computational routine --
129* -- LAPACK is a software package provided by Univ. of Tennessee, --
130* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
131*
132* .. Scalar Arguments ..
133 CHARACTER UPLO
134 INTEGER INFO, ITYPE, LDA, LDB, N
135* ..
136* .. Array Arguments ..
137 DOUBLE PRECISION A( LDA, * ), B( LDB, * )
138* ..
139*
140* =====================================================================
141*
142* .. Parameters ..
143 DOUBLE PRECISION ONE, HALF
144 parameter( one = 1.0d0, half = 0.5d0 )
145* ..
146* .. Local Scalars ..
147 LOGICAL UPPER
148 INTEGER K, KB, NB
149* ..
150* .. External Subroutines ..
151 EXTERNAL dsygs2, dsymm, dsyr2k, dtrmm, dtrsm, xerbla
152* ..
153* .. Intrinsic Functions ..
154 INTRINSIC max, min
155* ..
156* .. External Functions ..
157 LOGICAL LSAME
158 INTEGER ILAENV
159 EXTERNAL lsame, ilaenv
160* ..
161* .. Executable Statements ..
162*
163* Test the input parameters.
164*
165 info = 0
166 upper = lsame( uplo, 'U' )
167 IF( itype.LT.1 .OR. itype.GT.3 ) THEN
168 info = -1
169 ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
170 info = -2
171 ELSE IF( n.LT.0 ) THEN
172 info = -3
173 ELSE IF( lda.LT.max( 1, n ) ) THEN
174 info = -5
175 ELSE IF( ldb.LT.max( 1, n ) ) THEN
176 info = -7
177 END IF
178 IF( info.NE.0 ) THEN
179 CALL xerbla( 'DSYGST', -info )
180 RETURN
181 END IF
182*
183* Quick return if possible
184*
185 IF( n.EQ.0 )
186 $ RETURN
187*
188* Determine the block size for this environment.
189*
190 nb = ilaenv( 1, 'DSYGST', uplo, n, -1, -1, -1 )
191*
192 IF( nb.LE.1 .OR. nb.GE.n ) THEN
193*
194* Use unblocked code
195*
196 CALL dsygs2( itype, uplo, n, a, lda, b, ldb, info )
197 ELSE
198*
199* Use blocked code
200*
201 IF( itype.EQ.1 ) THEN
202 IF( upper ) THEN
203*
204* Compute inv(U**T)*A*inv(U)
205*
206 DO 10 k = 1, n, nb
207 kb = min( n-k+1, nb )
208*
209* Update the upper triangle of A(k:n,k:n)
210*
211 CALL dsygs2( itype, uplo, kb, a( k, k ), lda,
212 $ b( k, k ), ldb, info )
213 IF( k+kb.LE.n ) THEN
214 CALL dtrsm( 'Left', uplo, 'Transpose', 'Non-unit',
215 $ kb, n-k-kb+1, one, b( k, k ), ldb,
216 $ a( k, k+kb ), lda )
217 CALL dsymm( 'Left', uplo, kb, n-k-kb+1, -half,
218 $ a( k, k ), lda, b( k, k+kb ), ldb, one,
219 $ a( k, k+kb ), lda )
220 CALL dsyr2k( uplo, 'Transpose', n-k-kb+1, kb, -one,
221 $ a( k, k+kb ), lda, b( k, k+kb ), ldb,
222 $ one, a( k+kb, k+kb ), lda )
223 CALL dsymm( 'Left', uplo, kb, n-k-kb+1, -half,
224 $ a( k, k ), lda, b( k, k+kb ), ldb, one,
225 $ a( k, k+kb ), lda )
226 CALL dtrsm( 'Right', uplo, 'No transpose',
227 $ 'Non-unit', kb, n-k-kb+1, one,
228 $ b( k+kb, k+kb ), ldb, a( k, k+kb ),
229 $ lda )
230 END IF
231 10 CONTINUE
232 ELSE
233*
234* Compute inv(L)*A*inv(L**T)
235*
236 DO 20 k = 1, n, nb
237 kb = min( n-k+1, nb )
238*
239* Update the lower triangle of A(k:n,k:n)
240*
241 CALL dsygs2( itype, uplo, kb, a( k, k ), lda,
242 $ b( k, k ), ldb, info )
243 IF( k+kb.LE.n ) THEN
244 CALL dtrsm( 'Right', uplo, 'Transpose', 'Non-unit',
245 $ n-k-kb+1, kb, one, b( k, k ), ldb,
246 $ a( k+kb, k ), lda )
247 CALL dsymm( 'Right', uplo, n-k-kb+1, kb, -half,
248 $ a( k, k ), lda, b( k+kb, k ), ldb, one,
249 $ a( k+kb, k ), lda )
250 CALL dsyr2k( uplo, 'No transpose', n-k-kb+1, kb,
251 $ -one, a( k+kb, k ), lda, b( k+kb, k ),
252 $ ldb, one, a( k+kb, k+kb ), lda )
253 CALL dsymm( 'Right', uplo, n-k-kb+1, kb, -half,
254 $ a( k, k ), lda, b( k+kb, k ), ldb, one,
255 $ a( k+kb, k ), lda )
256 CALL dtrsm( 'Left', uplo, 'No transpose',
257 $ 'Non-unit', n-k-kb+1, kb, one,
258 $ b( k+kb, k+kb ), ldb, a( k+kb, k ),
259 $ lda )
260 END IF
261 20 CONTINUE
262 END IF
263 ELSE
264 IF( upper ) THEN
265*
266* Compute U*A*U**T
267*
268 DO 30 k = 1, n, nb
269 kb = min( n-k+1, nb )
270*
271* Update the upper triangle of A(1:k+kb-1,1:k+kb-1)
272*
273 CALL dtrmm( 'Left', uplo, 'No transpose', 'Non-unit',
274 $ k-1, kb, one, b, ldb, a( 1, k ), lda )
275 CALL dsymm( 'Right', uplo, k-1, kb, half, a( k, k ),
276 $ lda, b( 1, k ), ldb, one, a( 1, k ), lda )
277 CALL dsyr2k( uplo, 'No transpose', k-1, kb, one,
278 $ a( 1, k ), lda, b( 1, k ), ldb, one, a,
279 $ lda )
280 CALL dsymm( 'Right', uplo, k-1, kb, half, a( k, k ),
281 $ lda, b( 1, k ), ldb, one, a( 1, k ), lda )
282 CALL dtrmm( 'Right', uplo, 'Transpose', 'Non-unit',
283 $ k-1, kb, one, b( k, k ), ldb, a( 1, k ),
284 $ lda )
285 CALL dsygs2( itype, uplo, kb, a( k, k ), lda,
286 $ b( k, k ), ldb, info )
287 30 CONTINUE
288 ELSE
289*
290* Compute L**T*A*L
291*
292 DO 40 k = 1, n, nb
293 kb = min( n-k+1, nb )
294*
295* Update the lower triangle of A(1:k+kb-1,1:k+kb-1)
296*
297 CALL dtrmm( 'Right', uplo, 'No transpose', 'Non-unit',
298 $ kb, k-1, one, b, ldb, a( k, 1 ), lda )
299 CALL dsymm( 'Left', uplo, kb, k-1, half, a( k, k ),
300 $ lda, b( k, 1 ), ldb, one, a( k, 1 ), lda )
301 CALL dsyr2k( uplo, 'Transpose', k-1, kb, one,
302 $ a( k, 1 ), lda, b( k, 1 ), ldb, one, a,
303 $ lda )
304 CALL dsymm( 'Left', uplo, kb, k-1, half, a( k, k ),
305 $ lda, b( k, 1 ), ldb, one, a( k, 1 ), lda )
306 CALL dtrmm( 'Left', uplo, 'Transpose', 'Non-unit', kb,
307 $ k-1, one, b( k, k ), ldb, a( k, 1 ), lda )
308 CALL dsygs2( itype, uplo, kb, a( k, k ), lda,
309 $ b( k, k ), ldb, info )
310 40 CONTINUE
311 END IF
312 END IF
313 END IF
314 RETURN
315*
316* End of DSYGST
317*
318 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dsygs2(itype, uplo, n, a, lda, b, ldb, info)
DSYGS2 reduces a symmetric definite generalized eigenproblem to standard form, using the factorizatio...
Definition dsygs2.f:127
subroutine dsygst(itype, uplo, n, a, lda, b, ldb, info)
DSYGST
Definition dsygst.f:127
subroutine dsymm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)
DSYMM
Definition dsymm.f:189
subroutine dsyr2k(uplo, trans, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
DSYR2K
Definition dsyr2k.f:192
subroutine dtrmm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
DTRMM
Definition dtrmm.f:177
subroutine dtrsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
DTRSM
Definition dtrsm.f:181