LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ ssygst()

subroutine ssygst ( integer  itype,
character  uplo,
integer  n,
real, dimension( lda, * )  a,
integer  lda,
real, dimension( ldb, * )  b,
integer  ldb,
integer  info 
)

SSYGST

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

Purpose:
 SSYGST reduces a real symmetric-definite generalized eigenproblem
 to standard form.

 If ITYPE = 1, the problem is A*x = lambda*B*x,
 and A is overwritten by inv(U**T)*A*inv(U) or inv(L)*A*inv(L**T)

 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**T or L**T*A*L.

 B must have been previously factorized as U**T*U or L*L**T by SPOTRF.
Parameters
[in]ITYPE
          ITYPE is INTEGER
          = 1: compute inv(U**T)*A*inv(U) or inv(L)*A*inv(L**T);
          = 2 or 3: compute U*A*U**T or L**T*A*L.
[in]UPLO
          UPLO is CHARACTER*1
          = 'U':  Upper triangle of A is stored and B is factored as
                  U**T*U;
          = 'L':  Lower triangle of A is stored and B is factored as
                  L*L**T.
[in]N
          N is INTEGER
          The order of the matrices A and B.  N >= 0.
[in,out]A
          A is REAL array, dimension (LDA,N)
          On entry, the symmetric 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]B
          B is REAL array, dimension (LDB,N)
          The triangular factor from the Cholesky factorization of B,
          as returned by SPOTRF.
[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 126 of file ssygst.f.

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 REAL A( LDA, * ), B( LDB, * )
138* ..
139*
140* =====================================================================
141*
142* .. Parameters ..
143 REAL ONE, HALF
144 parameter( one = 1.0, half = 0.5 )
145* ..
146* .. Local Scalars ..
147 LOGICAL UPPER
148 INTEGER K, KB, NB
149* ..
150* .. External Subroutines ..
151 EXTERNAL ssygs2, ssymm, ssyr2k, strmm, strsm, 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( 'SSYGST', -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, 'SSYGST', uplo, n, -1, -1, -1 )
191*
192 IF( nb.LE.1 .OR. nb.GE.n ) THEN
193*
194* Use unblocked code
195*
196 CALL ssygs2( 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 ssygs2( itype, uplo, kb, a( k, k ), lda,
212 $ b( k, k ), ldb, info )
213 IF( k+kb.LE.n ) THEN
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 ),
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 ssygs2( itype, uplo, kb, a( k, k ), lda,
242 $ b( k, k ), ldb, info )
243 IF( k+kb.LE.n ) THEN
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 ),
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 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,
279 $ lda )
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 ),
284 $ lda )
285 CALL ssygs2( 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 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,
303 $ lda )
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 )
310 40 CONTINUE
311 END IF
312 END IF
313 END IF
314 RETURN
315*
316* End of SSYGST
317*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine ssygs2(itype, uplo, n, a, lda, b, ldb, info)
SSYGS2 reduces a symmetric definite generalized eigenproblem to standard form, using the factorizatio...
Definition ssygs2.f:127
subroutine ssymm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)
SSYMM
Definition ssymm.f:189
subroutine ssyr2k(uplo, trans, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
SSYR2K
Definition ssyr2k.f:192
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:162
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine strmm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
STRMM
Definition strmm.f:177
subroutine strsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
STRSM
Definition strsm.f:181
Here is the call graph for this function:
Here is the caller graph for this function: