dsbgst - reduce a real symmetric-definite banded generalized eigenproblem A*x = lambda*B*x to standard form C*y = lambda*y,
SUBROUTINE DSBGST( VECT, UPLO, N, KA, KB, AB, LDAB, BB, LDBB, X, * LDX, WORK, INFO) CHARACTER * 1 VECT, UPLO INTEGER N, KA, KB, LDAB, LDBB, LDX, INFO DOUBLE PRECISION AB(LDAB,*), BB(LDBB,*), X(LDX,*), WORK(*)
SUBROUTINE DSBGST_64( VECT, UPLO, N, KA, KB, AB, LDAB, BB, LDBB, X, * LDX, WORK, INFO) CHARACTER * 1 VECT, UPLO INTEGER*8 N, KA, KB, LDAB, LDBB, LDX, INFO DOUBLE PRECISION AB(LDAB,*), BB(LDBB,*), X(LDX,*), WORK(*)
SUBROUTINE SBGST( VECT, UPLO, [N], KA, KB, AB, [LDAB], BB, [LDBB], * X, [LDX], [WORK], [INFO]) CHARACTER(LEN=1) :: VECT, UPLO INTEGER :: N, KA, KB, LDAB, LDBB, LDX, INFO REAL(8), DIMENSION(:) :: WORK REAL(8), DIMENSION(:,:) :: AB, BB, X
SUBROUTINE SBGST_64( VECT, UPLO, [N], KA, KB, AB, [LDAB], BB, [LDBB], * X, [LDX], [WORK], [INFO]) CHARACTER(LEN=1) :: VECT, UPLO INTEGER(8) :: N, KA, KB, LDAB, LDBB, LDX, INFO REAL(8), DIMENSION(:) :: WORK REAL(8), DIMENSION(:,:) :: AB, BB, X
#include <sunperf.h>
void dsbgst(char vect, char uplo, int n, int ka, int kb, double *ab, int ldab, double *bb, int ldbb, double *x, int ldx, int *info);
void dsbgst_64(char vect, char uplo, long n, long ka, long kb, double *ab, long ldab, double *bb, long ldbb, double *x, long ldx, long *info);
dsbgst reduces a real symmetric-definite banded generalized eigenproblem A*x = lambda*B*x to standard form C*y = lambda*y, such that C has the same bandwidth as A.
B must have been previously factorized as S**T*S by SPBSTF, using a split Cholesky factorization. A is overwritten by C = X**T*A*X, where X = S**(-1)*Q and Q is an orthogonal matrix chosen to preserve the bandwidth of A.
= 'N': do not form the transformation matrix X;
= 'V': form X.
= 'U': Upper triangle of A is stored;
= 'L': Lower triangle of A is stored.
AB(ka+1+i-j,j)
= A(i,j)
for max(1,j-ka)
< =i < =j;
if UPLO = 'L', AB(1+i-j,j)
= A(i,j)
for j < =i < =min(n,j+ka).
On exit, the transformed matrix X**T*A*X, stored in the same format as A.
max(1,N)
if VECT = 'V'; LDX > = 1 otherwise.
dimension(2*N)
= 0: successful exit
< 0: if INFO = -i, the i-th argument had an illegal value.