NAME

ssygv - compute all the eigenvalues, and optionally, the eigenvectors of a real generalized symmetric-definite eigenproblem, of the form A*x=(lambda)*B*x, A*Bx=(lambda)*x, or B*A*x=(lambda)*x


SYNOPSIS

  SUBROUTINE SSYGV( ITYPE, JOBZ, UPLO, N, A, LDA, B, LDB, W, WORK, 
 *      LDWORK, INFO)
  CHARACTER * 1 JOBZ, UPLO
  INTEGER ITYPE, N, LDA, LDB, LDWORK, INFO
  REAL A(LDA,*), B(LDB,*), W(*), WORK(*)
  SUBROUTINE SSYGV_64( ITYPE, JOBZ, UPLO, N, A, LDA, B, LDB, W, WORK, 
 *      LDWORK, INFO)
  CHARACTER * 1 JOBZ, UPLO
  INTEGER*8 ITYPE, N, LDA, LDB, LDWORK, INFO
  REAL A(LDA,*), B(LDB,*), W(*), WORK(*)

F95 INTERFACE

  SUBROUTINE SYGV( ITYPE, JOBZ, UPLO, [N], A, [LDA], B, [LDB], W, 
 *       [WORK], [LDWORK], [INFO])
  CHARACTER(LEN=1) :: JOBZ, UPLO
  INTEGER :: ITYPE, N, LDA, LDB, LDWORK, INFO
  REAL, DIMENSION(:) :: W, WORK
  REAL, DIMENSION(:,:) :: A, B
  SUBROUTINE SYGV_64( ITYPE, JOBZ, UPLO, [N], A, [LDA], B, [LDB], W, 
 *       [WORK], [LDWORK], [INFO])
  CHARACTER(LEN=1) :: JOBZ, UPLO
  INTEGER(8) :: ITYPE, N, LDA, LDB, LDWORK, INFO
  REAL, DIMENSION(:) :: W, WORK
  REAL, DIMENSION(:,:) :: A, B

C INTERFACE

#include <sunperf.h>

void ssygv(int itype, char jobz, char uplo, int n, float *a, int lda, float *b, int ldb, float *w, int *info);

void ssygv_64(long itype, char jobz, char uplo, long n, float *a, long lda, float *b, long ldb, float *w, long *info);


PURPOSE

ssygv computes all the eigenvalues, and optionally, the eigenvectors of a real generalized symmetric-definite eigenproblem, of the form A*x=(lambda)*B*x, A*Bx=(lambda)*x, or B*A*x=(lambda)*x. Here A and B are assumed to be symmetric and B is also

positive definite.


ARGUMENTS