126 SUBROUTINE ssygst( ITYPE, UPLO, N, A, LDA, B, LDB, INFO )
134 INTEGER INFO, ITYPE, LDA, LDB, N
137 REAL A( LDA, * ), B( LDB, * )
144 parameter( one = 1.0, half = 0.5 )
159 EXTERNAL lsame, ilaenv
166 upper = lsame( uplo,
'U' )
167 IF( itype.LT.1 .OR. itype.GT.3 )
THEN
169 ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo,
'L' ) )
THEN
171 ELSE IF( n.LT.0 )
THEN
173 ELSE IF( lda.LT.max( 1, n ) )
THEN
175 ELSE IF( ldb.LT.max( 1, n ) )
THEN
179 CALL xerbla(
'SSYGST', -info )
190 nb = ilaenv( 1,
'SSYGST', uplo, n, -1, -1, -1 )
192 IF( nb.LE.1 .OR. nb.GE.n )
THEN
196 CALL ssygs2( itype, uplo, n, a, lda, b, ldb, info )
201 IF( itype.EQ.1 )
THEN
207 kb = min( n-k+1, nb )
211 CALL ssygs2( itype, uplo, kb, a( k, k ), lda,
212 $ b( k, k ), ldb, info )
214 CALL strsm(
'Left', uplo,
'Transpose',
'Non-unit',
215 $ kb, n-k-kb+1, one, b( k, k ), ldb,
216 $ a( k, k+kb ), lda )
217 CALL ssymm(
'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 ssyr2k( 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 ssymm(
'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 strsm(
'Right', uplo,
'No transpose',
227 $
'Non-unit', kb, n-k-kb+1, one,
228 $ b( k+kb, k+kb ), ldb, a( k, k+kb ),
237 kb = min( n-k+1, nb )
241 CALL ssygs2( itype, uplo, kb, a( k, k ), lda,
242 $ b( k, k ), ldb, info )
244 CALL strsm(
'Right', uplo,
'Transpose',
'Non-unit',
245 $ n-k-kb+1, kb, one, b( k, k ), ldb,
246 $ a( k+kb, k ), lda )
247 CALL ssymm(
'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 ssyr2k( 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 ssymm(
'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 strsm(
'Left', uplo,
'No transpose',
257 $
'Non-unit', n-k-kb+1, kb, one,
258 $ b( k+kb, k+kb ), ldb, a( k+kb, k ),
269 kb = min( n-k+1, nb )
273 CALL strmm(
'Left', uplo,
'No transpose',
'Non-unit',
274 $ k-1, kb, one, b, ldb, a( 1, k ), lda )
275 CALL ssymm(
'Right', uplo, k-1, kb, half, a( k, k ),
276 $ lda, b( 1, k ), ldb, one, a( 1, k ), lda )
277 CALL ssyr2k( uplo,
'No transpose', k-1, kb, one,
278 $ a( 1, k ), lda, b( 1, k ), ldb, one, a,
280 CALL ssymm(
'Right', uplo, k-1, kb, half, a( k, k ),
281 $ lda, b( 1, k ), ldb, one, a( 1, k ), lda )
282 CALL strmm(
'Right', uplo,
'Transpose',
'Non-unit',
283 $ k-1, kb, one, b( k, k ), ldb, a( 1, k ),
285 CALL ssygs2( itype, uplo, kb, a( k, k ), lda,
286 $ b( k, k ), ldb, info )
293 kb = min( n-k+1, nb )
297 CALL strmm(
'Right', uplo,
'No transpose',
'Non-unit',
298 $ kb, k-1, one, b, ldb, a( k, 1 ), lda )
299 CALL ssymm(
'Left', uplo, kb, k-1, half, a( k, k ),
300 $ lda, b( k, 1 ), ldb, one, a( k, 1 ), lda )
301 CALL ssyr2k( uplo,
'Transpose', k-1, kb, one,
302 $ a( k, 1 ), lda, b( k, 1 ), ldb, one, a,
304 CALL ssymm(
'Left', uplo, kb, k-1, half, a( k, k ),
305 $ lda, b( k, 1 ), ldb, one, a( k, 1 ), lda )
306 CALL strmm(
'Left', uplo,
'Transpose',
'Non-unit', kb,
307 $ k-1, one, b( k, k ), ldb, a( k, 1 ), lda )
308 CALL ssygs2( itype, uplo, kb, a( k, k ), lda,
309 $ b( k, k ), ldb, info )
subroutine xerbla(srname, info)
subroutine ssygs2(itype, uplo, n, a, lda, b, ldb, info)
SSYGS2 reduces a symmetric definite generalized eigenproblem to standard form, using the factorizatio...
subroutine ssygst(itype, uplo, n, a, lda, b, ldb, info)
SSYGST
subroutine ssymm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)
SSYMM
subroutine ssyr2k(uplo, trans, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
SSYR2K
subroutine strmm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
STRMM
subroutine strsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
STRSM