Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cheevx (3p)

Name

cheevx - compute selected eigenvalues and, optionally, eigenvectors of a complex Hermitian matrix A

Synopsis

SUBROUTINE CHEEVX(JOBZ, RANGE, UPLO, N, A, LDA, VL, VU, IL, IU,
ABTOL, NFOUND, W, Z, LDZ, WORK, LDWORK, WORK2, IWORK3, IFAIL,
INFO)

CHARACTER*1 JOBZ, RANGE, UPLO
COMPLEX A(LDA,*), Z(LDZ,*), WORK(*)
INTEGER N, LDA, IL, IU, NFOUND, LDZ, LDWORK, INFO
INTEGER IWORK3(*), IFAIL(*)
REAL VL, VU, ABTOL
REAL W(*), WORK2(*)

SUBROUTINE CHEEVX_64(JOBZ, RANGE, UPLO, N, A, LDA, VL, VU, IL, IU,
ABTOL, NFOUND, W, Z, LDZ, WORK, LDWORK, WORK2, IWORK3, IFAIL,
INFO)

CHARACTER*1 JOBZ, RANGE, UPLO
COMPLEX A(LDA,*), Z(LDZ,*), WORK(*)
INTEGER*8 N, LDA, IL, IU, NFOUND, LDZ, LDWORK, INFO
INTEGER*8 IWORK3(*), IFAIL(*)
REAL VL, VU, ABTOL
REAL W(*), WORK2(*)




F95 INTERFACE
SUBROUTINE HEEVX(JOBZ, RANGE, UPLO, N, A, LDA, VL, VU, IL, IU,
ABTOL, NFOUND, W, Z, LDZ, WORK, LDWORK, WORK2, IWORK3,
IFAIL, INFO)

CHARACTER(LEN=1) :: JOBZ, RANGE, UPLO
COMPLEX, DIMENSION(:) :: WORK
COMPLEX, DIMENSION(:,:) :: A, Z
INTEGER :: N, LDA, IL, IU, NFOUND, LDZ, LDWORK, INFO
INTEGER, DIMENSION(:) :: IWORK3, IFAIL
REAL :: VL, VU, ABTOL
REAL, DIMENSION(:) :: W, WORK2

SUBROUTINE HEEVX_64(JOBZ, RANGE, UPLO, N, A, LDA, VL, VU, IL, IU,
ABTOL, NFOUND, W, Z, LDZ, WORK, LDWORK, WORK2, IWORK3,
IFAIL, INFO)

CHARACTER(LEN=1) :: JOBZ, RANGE, UPLO
COMPLEX, DIMENSION(:) :: WORK
COMPLEX, DIMENSION(:,:) :: A, Z
INTEGER(8) :: N, LDA, IL, IU, NFOUND, LDZ, LDWORK, INFO
INTEGER(8), DIMENSION(:) :: IWORK3, IFAIL
REAL :: VL, VU, ABTOL
REAL, DIMENSION(:) :: W, WORK2




C INTERFACE
#include <sunperf.h>

void cheevx(char jobz, char range, char uplo, int n,  complex  *a,  int
lda,  float  vl,  float  vu, int il, int iu, float abtol, int
*nfound, float *w, complex  *z,  int  ldz,  int  *ifail,  int
*info);

void  cheevx_64(char  jobz,  char range, char uplo, long n, complex *a,
long lda, float vl, float vu, long il, long iu, float  abtol,
long  *nfound,  float  *w, complex *z, long ldz, long *ifail,
long *info);

Description

Oracle Solaris Studio Performance Library                           cheevx(3P)



NAME
       cheevx  - compute selected eigenvalues and, optionally, eigenvectors of
       a complex Hermitian matrix A


SYNOPSIS
       SUBROUTINE CHEEVX(JOBZ, RANGE, UPLO, N, A, LDA, VL, VU, IL, IU,
             ABTOL, NFOUND, W, Z, LDZ, WORK, LDWORK, WORK2, IWORK3, IFAIL,
             INFO)

       CHARACTER*1 JOBZ, RANGE, UPLO
       COMPLEX A(LDA,*), Z(LDZ,*), WORK(*)
       INTEGER N, LDA, IL, IU, NFOUND, LDZ, LDWORK, INFO
       INTEGER IWORK3(*), IFAIL(*)
       REAL VL, VU, ABTOL
       REAL W(*), WORK2(*)

       SUBROUTINE CHEEVX_64(JOBZ, RANGE, UPLO, N, A, LDA, VL, VU, IL, IU,
             ABTOL, NFOUND, W, Z, LDZ, WORK, LDWORK, WORK2, IWORK3, IFAIL,
             INFO)

       CHARACTER*1 JOBZ, RANGE, UPLO
       COMPLEX A(LDA,*), Z(LDZ,*), WORK(*)
       INTEGER*8 N, LDA, IL, IU, NFOUND, LDZ, LDWORK, INFO
       INTEGER*8 IWORK3(*), IFAIL(*)
       REAL VL, VU, ABTOL
       REAL W(*), WORK2(*)




   F95 INTERFACE
       SUBROUTINE HEEVX(JOBZ, RANGE, UPLO, N, A, LDA, VL, VU, IL, IU,
              ABTOL, NFOUND, W, Z, LDZ, WORK, LDWORK, WORK2, IWORK3,
              IFAIL, INFO)

       CHARACTER(LEN=1) :: JOBZ, RANGE, UPLO
       COMPLEX, DIMENSION(:) :: WORK
       COMPLEX, DIMENSION(:,:) :: A, Z
       INTEGER :: N, LDA, IL, IU, NFOUND, LDZ, LDWORK, INFO
       INTEGER, DIMENSION(:) :: IWORK3, IFAIL
       REAL :: VL, VU, ABTOL
       REAL, DIMENSION(:) :: W, WORK2

       SUBROUTINE HEEVX_64(JOBZ, RANGE, UPLO, N, A, LDA, VL, VU, IL, IU,
              ABTOL, NFOUND, W, Z, LDZ, WORK, LDWORK, WORK2, IWORK3,
              IFAIL, INFO)

       CHARACTER(LEN=1) :: JOBZ, RANGE, UPLO
       COMPLEX, DIMENSION(:) :: WORK
       COMPLEX, DIMENSION(:,:) :: A, Z
       INTEGER(8) :: N, LDA, IL, IU, NFOUND, LDZ, LDWORK, INFO
       INTEGER(8), DIMENSION(:) :: IWORK3, IFAIL
       REAL :: VL, VU, ABTOL
       REAL, DIMENSION(:) :: W, WORK2




   C INTERFACE
       #include <sunperf.h>

       void cheevx(char jobz, char range, char uplo, int n,  complex  *a,  int
                 lda,  float  vl,  float  vu, int il, int iu, float abtol, int
                 *nfound, float *w, complex  *z,  int  ldz,  int  *ifail,  int
                 *info);

       void  cheevx_64(char  jobz,  char range, char uplo, long n, complex *a,
                 long lda, float vl, float vu, long il, long iu, float  abtol,
                 long  *nfound,  float  *w, complex *z, long ldz, long *ifail,
                 long *info);



PURPOSE
       cheevx computes selected eigenvalues and, optionally, eigenvectors of a
       complex  Hermitian  matrix  A.   Eigenvalues  and  eigenvectors  can be
       selected by specifying either a range of values or a range  of  indices
       for the desired eigenvalues.


ARGUMENTS
       JOBZ (input)
                 = 'N':  Compute eigenvalues only;
                 = 'V':  Compute eigenvalues and eigenvectors.


       RANGE (input)
                 = 'A': all eigenvalues will be found.
                 = 'V': all eigenvalues in the half-open interval (VL,VU] will
                 be found.  = 'I': the IL-th through IU-th eigenvalues will be
                 found.


       UPLO (input)
                 = 'U':  Upper triangle of A is stored;
                 = 'L':  Lower triangle of A is stored.


       N (input) The order of the matrix A.  N >= 0.


       A (input/output)
                 On entry, the Hermitian matrix A.  If UPLO = 'U', the leading
                 N-by-N upper triangular part of A contains the upper triangu-
                 lar  part of the matrix A.  If UPLO = 'L', the leading N-by-N
                 lower triangular part of A contains the lower triangular part
                 of  the  matrix A.  On exit, the lower triangle (if UPLO='L')
                 or the upper triangle (if UPLO='U') of A, including the diag-
                 onal, is destroyed.


       LDA (input)
                 The leading dimension of the array A.  LDA >= max(1,N).


       VL (input)
                 If  RANGE='V',  the lower and upper bounds of the interval to
                 be searched for eigenvalues. VL  <  VU.   Not  referenced  if
                 RANGE = 'A' or 'I'.


       VU (input)
                 If  RANGE='V',  the lower and upper bounds of the interval to
                 be searched for eigenvalues. VL  <  VU.   Not  referenced  if
                 RANGE = 'A' or 'I'.


       IL (input)
                 If  RANGE='I', the indices (in ascending order) of the small-
                 est and largest eigenvalues to be returned.  1 <= IL <= IU <=
                 N,  if  N > 0; IL = 1 and IU = 0 if N = 0.  Not referenced if
                 RANGE = 'A' or 'V'.


       IU (input)
                 If RANGE='I', the indices (in ascending order) of the  small-
                 est and largest eigenvalues to be returned.  1 <= IL <= IU <=
                 N, if N > 0; IL = 1 and IU = 0 if N = 0.  Not  referenced  if
                 RANGE = 'A' or 'V'.


       ABTOL (input)
                 The absolute error tolerance for the eigenvalues.  An approx-
                 imate eigenvalue is accepted as converged when it  is  deter-
                 mined to lie in an interval [a,b] of width less than or equal
                 to

                 ABTOL + EPS *   max( |a|,|b| ) ,

                 where EPS is the machine precision.  If ABTOL is less than or
                 equal  to  zero,  then   EPS*|T|   will be used in its place,
                 where |T| is the 1-norm of the tridiagonal matrix obtained by
                 reducing A to tridiagonal form.

                 Eigenvalues  will  be  computed most accurately when ABTOL is
                 set to twice the underflow threshold 2*SLAMCH('S'), not zero.
                 If  this  routine  returns  with INFO>0, indicating that some
                 eigenvectors  did  not  converge,  try   setting   ABTOL   to
                 2*SLAMCH('S').

                 See  "Computing  Small Singular Values of Bidiagonal Matrices
                 with Guaranteed High Relative Accuracy," by Demmel and Kahan,
                 LAPACK Working Note #3.


       NFOUND (output)
                 The total number of eigenvalues found.  0 <= NFOUND <= N.  If
                 RANGE = 'A', NFOUND = N, and if RANGE =  'I',  NFOUND  =  IU-
                 IL+1.


       W (output)
                 On  normal  exit,  the  first  NFOUND  elements  contain  the
                 selected eigenvalues in ascending order.


       Z (output)
                 If JOBZ = 'V', then if INFO = 0, the first NFOUND columns  of
                 Z contain the orthonormal eigenvectors of the matrix A corre-
                 sponding to the selected eigenvalues, with the i-th column of
                 Z holding the eigenvector associated with W(i).  If an eigen-
                 vector fails to converge, then that column of Z contains  the
                 latest approximation to the eigenvector, and the index of the
                 eigenvector is returned in IFAIL.  If JOBZ = 'N', then  Z  is
                 not  referenced.   Note:  the  user must ensure that at least
                 max(1,NFOUND) columns are supplied in the array Z; if RANGE =
                 'V', the exact value of NFOUND is not known in advance and an
                 upper bound must be used.


       LDZ (input)
                 The leading dimension of the array Z.  LDZ >= 1, and if  JOBZ
                 = 'V', LDZ >= max(1,N).


       WORK (workspace)
                 On exit, if INFO = 0, WORK(1) returns the optimal LDWORK.


       LDWORK (input)
                 The  length  of  the  array WORK.  LDWORK >= max(1,2*N).  For
                 optimal efficiency, LDWORK >= (NB+1)*N, where NB is  the  max
                 of  the  blocksize  for  CHETRD and for CUNMTR as returned by
                 ILAENV.

                 If LDWORK = -1, then a workspace query is assumed;  the  rou-
                 tine  only  calculates  the  optimal  size of the WORK array,
                 returns this value as the first entry of the WORK array,  and
                 no error message related to LDWORK is issued by XERBLA.


       WORK2 (workspace)
                 dimension(7*N)


       IWORK3 (workspace)
                 dimension(5*N)


       IFAIL (output)
                 If JOBZ = 'V', then if INFO = 0, the first NFOUND elements of
                 IFAIL are zero.  If INFO > 0, then IFAIL contains the indices
                 of  the eigenvectors that failed to converge.  If JOBZ = 'N',
                 then IFAIL is not referenced.


       INFO (output)
                 = 0:  successful exit
                 < 0:  if INFO = -i, the i-th argument had an illegal value
                 > 0:  if INFO = i, then i eigenvectors  failed  to  converge.
                 Their indices are stored in array IFAIL.




                                  7 Nov 2015                        cheevx(3P)