NAME

zhbgvx - compute all the eigenvalues, and optionally, the eigenvectors of a complex generalized Hermitian-definite banded eigenproblem, of the form A*x=(lambda)*B*x


SYNOPSIS

  SUBROUTINE ZHBGVX( JOBZ, RANGE, UPLO, N, KA, KB, AB, LDAB, BB, LDBB, 
 *      Q, LDQ, VL, VU, IL, IU, ABSTOL, M, W, Z, LDZ, WORK, RWORK, IWORK, 
 *      IFAIL, INFO)
  CHARACTER * 1 JOBZ, RANGE, UPLO
  DOUBLE COMPLEX AB(LDAB,*), BB(LDBB,*), Q(LDQ,*), Z(LDZ,*), WORK(*)
  INTEGER N, KA, KB, LDAB, LDBB, LDQ, IL, IU, M, LDZ, INFO
  INTEGER IWORK(*), IFAIL(*)
  DOUBLE PRECISION VL, VU, ABSTOL
  DOUBLE PRECISION W(*), RWORK(*)
  SUBROUTINE ZHBGVX_64( JOBZ, RANGE, UPLO, N, KA, KB, AB, LDAB, BB, 
 *      LDBB, Q, LDQ, VL, VU, IL, IU, ABSTOL, M, W, Z, LDZ, WORK, RWORK, 
 *      IWORK, IFAIL, INFO)
  CHARACTER * 1 JOBZ, RANGE, UPLO
  DOUBLE COMPLEX AB(LDAB,*), BB(LDBB,*), Q(LDQ,*), Z(LDZ,*), WORK(*)
  INTEGER*8 N, KA, KB, LDAB, LDBB, LDQ, IL, IU, M, LDZ, INFO
  INTEGER*8 IWORK(*), IFAIL(*)
  DOUBLE PRECISION VL, VU, ABSTOL
  DOUBLE PRECISION W(*), RWORK(*)

F95 INTERFACE

  SUBROUTINE HBGVX( JOBZ, RANGE, UPLO, [N], KA, KB, AB, [LDAB], BB, 
 *       [LDBB], Q, [LDQ], VL, VU, IL, IU, ABSTOL, M, W, Z, [LDZ], [WORK], 
 *       [RWORK], [IWORK], IFAIL, [INFO])
  CHARACTER(LEN=1) :: JOBZ, RANGE, UPLO
  COMPLEX(8), DIMENSION(:) :: WORK
  COMPLEX(8), DIMENSION(:,:) :: AB, BB, Q, Z
  INTEGER :: N, KA, KB, LDAB, LDBB, LDQ, IL, IU, M, LDZ, INFO
  INTEGER, DIMENSION(:) :: IWORK, IFAIL
  REAL(8) :: VL, VU, ABSTOL
  REAL(8), DIMENSION(:) :: W, RWORK
  SUBROUTINE HBGVX_64( JOBZ, RANGE, UPLO, [N], KA, KB, AB, [LDAB], BB, 
 *       [LDBB], Q, [LDQ], VL, VU, IL, IU, ABSTOL, M, W, Z, [LDZ], [WORK], 
 *       [RWORK], [IWORK], IFAIL, [INFO])
  CHARACTER(LEN=1) :: JOBZ, RANGE, UPLO
  COMPLEX(8), DIMENSION(:) :: WORK
  COMPLEX(8), DIMENSION(:,:) :: AB, BB, Q, Z
  INTEGER(8) :: N, KA, KB, LDAB, LDBB, LDQ, IL, IU, M, LDZ, INFO
  INTEGER(8), DIMENSION(:) :: IWORK, IFAIL
  REAL(8) :: VL, VU, ABSTOL
  REAL(8), DIMENSION(:) :: W, RWORK

C INTERFACE

#include <sunperf.h>

void zhbgvx(char jobz, char range, char uplo, int n, int ka, int kb, doublecomplex *ab, int ldab, doublecomplex *bb, int ldbb, doublecomplex *q, int ldq, double vl, double vu, int il, int iu, double abstol, int *m, double *w, doublecomplex *z, int ldz, int *ifail, int *info);

void zhbgvx_64(char jobz, char range, char uplo, long n, long ka, long kb, doublecomplex *ab, long ldab, doublecomplex *bb, long ldbb, doublecomplex *q, long ldq, double vl, double vu, long il, long iu, double abstol, long *m, double *w, doublecomplex *z, long ldz, long *ifail, long *info);


PURPOSE

zhbgvx computes all the eigenvalues, and optionally, the eigenvectors of a complex generalized Hermitian-definite banded eigenproblem, of the form A*x=(lambda)*B*x. Here A and B are assumed to be Hermitian and banded, and B is also positive definite. Eigenvalues and eigenvectors can be selected by specifying either all eigenvalues, a range of values or a range of indices for the desired eigenvalues.


ARGUMENTS


FURTHER DETAILS

Based on contributions by

   Mark Fahey, Department of Mathematics, Univ. of Kentucky, USA