Contents


NAME

     dspevx  -  compute  selected  eigenvalues  and,  optionally,
     eigenvectors of a real symmetric matrix A in packed storage

SYNOPSIS

     SUBROUTINE DSPEVX(JOBZ, RANGE, UPLO, N, AP, VL, VU, IL, IU, ABTOL,
           NFOUND, W, Z, LDZ, WORK, IWORK2, IFAIL, INFO)

     CHARACTER * 1 JOBZ, RANGE, UPLO
     INTEGER N, IL, IU, NFOUND, LDZ, INFO
     INTEGER IWORK2(*), IFAIL(*)
     DOUBLE PRECISION VL, VU, ABTOL
     DOUBLE PRECISION AP(*), W(*), Z(LDZ,*), WORK(*)

     SUBROUTINE DSPEVX_64(JOBZ, RANGE, UPLO, N, AP, VL, VU, IL, IU, ABTOL,
           NFOUND, W, Z, LDZ, WORK, IWORK2, IFAIL, INFO)

     CHARACTER * 1 JOBZ, RANGE, UPLO
     INTEGER*8 N, IL, IU, NFOUND, LDZ, INFO
     INTEGER*8 IWORK2(*), IFAIL(*)
     DOUBLE PRECISION VL, VU, ABTOL
     DOUBLE PRECISION AP(*), W(*), Z(LDZ,*), WORK(*)

  F95 INTERFACE
     SUBROUTINE SPEVX(JOBZ, RANGE, UPLO, N, AP, VL, VU, IL, IU, ABTOL,
            NFOUND, W, Z, [LDZ], [WORK], [IWORK2], IFAIL, [INFO])

     CHARACTER(LEN=1) :: JOBZ, RANGE, UPLO
     INTEGER :: N, IL, IU, NFOUND, LDZ, INFO
     INTEGER, DIMENSION(:) :: IWORK2, IFAIL
     REAL(8) :: VL, VU, ABTOL
     REAL(8), DIMENSION(:) :: AP, W, WORK
     REAL(8), DIMENSION(:,:) :: Z

     SUBROUTINE SPEVX_64(JOBZ, RANGE, UPLO, N, AP, VL, VU, IL, IU, ABTOL,
            NFOUND, W, Z, [LDZ], [WORK], [IWORK2], IFAIL, [INFO])

     CHARACTER(LEN=1) :: JOBZ, RANGE, UPLO
     INTEGER(8) :: N, IL, IU, NFOUND, LDZ, INFO
     INTEGER(8), DIMENSION(:) :: IWORK2, IFAIL
     REAL(8) :: VL, VU, ABTOL
     REAL(8), DIMENSION(:) :: AP, W, WORK
     REAL(8), DIMENSION(:,:) :: Z

  C INTERFACE
     #include <sunperf.h>
     void dspevx(char jobz, char range, char uplo, int n,  double
               *ap,  double vl, double vu, int il, int iu, double
               abtol, int *nfound, double *w, double *z, int ldz,
               int *ifail, int *info);

     void dspevx_64(char jobz, char range,  char  uplo,  long  n,
               double  *ap,  double  vl, double vu, long il, long
               iu, double abtol, long *nfound, double *w,  double
               *z, long ldz, long *ifail, long *info);

PURPOSE

     dspevx computes selected eigenvalues and, optionally, eigen-
     vectors  of  a  real  symmetric  matrix A in packed storage.
     Eigenvalues/vectors can be selected by specifying  either  a
     range of values or a range of indices for the desired eigen-
     values.

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.

     AP (input/output)
               Double precision array, dimension  (N*(N+1)/2)  On
               entry,  the  upper  or  lower triangle of the sym-
               metric matrix A, packed  columnwise  in  a  linear
               array.   The  j-th  column  of  A is stored in the
               array AP as follows:  if UPLO = 'U',  AP(i  +  (j-
               1)*j/2)  = A(i,j) for 1<=i<=j; if UPLO = 'L', AP(i
               + (j-1)*(2*n-j)/2) = A(i,j) for j<=i<=n.

               On exit, AP is  overwritten  by  values  generated
               during the reduction to tridiagonal form.  If UPLO
               = 'U', the diagonal and first superdiagonal of the
               tridiagonal  matrix  T overwrite the corresponding
               elements of A, and if UPLO = 'L', the diagonal and
               first subdiagonal of T overwrite the corresponding
               elements of A.

     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)
               See the description of VL.

     IL (input)
               If RANGE='I', the indices (in ascending order)  of
               the   smallest   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)
               See the description of IL.

     ABTOL (input)
               The absolute error tolerance for the  eigenvalues.
               An approximate eigenvalue is accepted as converged
               when it is determined 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 AP to tri-
               diagonal 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)
               Double precision array, dimension (N) If INFO = 0,
               the selected eigenvalues in ascending order.

     Z (output)
               Double precision array, dimension (LDZ,  max(1,M))
               If  JOBZ = 'V', then if INFO = 0, the first NFOUND
               columns of Z contain the orthonormal  eigenvectors
               of  the  matrix  A  corresponding  to the selected
               eigenvalues, with the i-th column of Z holding the
               eigenvector associated with W(i).  If an eigenvec-
               tor fails to converge, then that column of Z  con-
               tains 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)
               Double precision array, dimension(8*N)

     IWORK2 (workspace)
               Integer array, dimension(5*N)

     IFAIL (output)
               Integer array, dimension(N) 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 con-
               verge.  If JOBZ = 'N', then IFAIL  is  not  refer-
               enced.

     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.