Contents


NAME

     dspevd - compute all the eigenvalues and, optionally, eigen-
     vectors of a real symmetric matrix A in packed storage

SYNOPSIS

     SUBROUTINE DSPEVD(JOBZ, UPLO, N, AP, W, Z, LDZ, WORK, LWORK, IWORK,
           LIWORK, INFO)

     CHARACTER * 1 JOBZ, UPLO
     INTEGER N, LDZ, LWORK, LIWORK, INFO
     INTEGER IWORK(*)
     DOUBLE PRECISION AP(*), W(*), Z(LDZ,*), WORK(*)

     SUBROUTINE DSPEVD_64(JOBZ, UPLO, N, AP, W, Z, LDZ, WORK, LWORK,
           IWORK, LIWORK, INFO)

     CHARACTER * 1 JOBZ, UPLO
     INTEGER*8 N, LDZ, LWORK, LIWORK, INFO
     INTEGER*8 IWORK(*)
     DOUBLE PRECISION AP(*), W(*), Z(LDZ,*), WORK(*)

  F95 INTERFACE
     SUBROUTINE SPEVD(JOBZ, UPLO, [N], AP, W, Z, [LDZ], [WORK], [LWORK],
            [IWORK], [LIWORK], [INFO])

     CHARACTER(LEN=1) :: JOBZ, UPLO
     INTEGER :: N, LDZ, LWORK, LIWORK, INFO
     INTEGER, DIMENSION(:) :: IWORK
     REAL(8), DIMENSION(:) :: AP, W, WORK
     REAL(8), DIMENSION(:,:) :: Z

     SUBROUTINE SPEVD_64(JOBZ, UPLO, [N], AP, W, Z, [LDZ], [WORK], [LWORK],
            [IWORK], [LIWORK], [INFO])

     CHARACTER(LEN=1) :: JOBZ, UPLO
     INTEGER(8) :: N, LDZ, LWORK, LIWORK, INFO
     INTEGER(8), DIMENSION(:) :: IWORK
     REAL(8), DIMENSION(:) :: AP, W, WORK
     REAL(8), DIMENSION(:,:) :: Z

  C INTERFACE
     #include <sunperf.h>

     void dspevd(char jobz, char uplo, int n, double *ap,  double
               *w, double *z, int ldz, int *info);
     void dspevd_64(char jobz, char uplo,  long  n,  double  *ap,
               double *w, double *z, long ldz, long *info);

PURPOSE

     dspevd computes all the eigenvalues and, optionally,  eigen-
     vectors  of  a real symmetric matrix A in packed storage. If
     eigenvectors are desired, it uses a divide and conquer algo-
     rithm.

     The divide and conquer algorithm makes very mild assumptions
     about  floating  point  arithmetic. It will work on machines
     with a guard digit  in  add/subtract,  or  on  those  binary
     machines  without  guard digits which subtract like the Cray
     X-MP, Cray Y-MP, Cray C-90, or Cray-2. It could  conceivably
     fail  on  hexadecimal  or  decimal  machines  without  guard
     digits, but we know of none.

ARGUMENTS

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

     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.
     W (output)
               Double precision array, dimension (N) If INFO = 0,
               the eigenvalues in ascending order.

     Z (input) Double precision array, dimension (LDZ, N) If JOBZ
               =  'V', then if INFO = 0, Z contains the orthonor-
               mal eigenvectors of the matrix A,  with  the  i-th
               column  of  Z  holding  the eigenvector associated
               with W(i).  If JOBZ = 'N', then Z  is  not  refer-
               enced.

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

     WORK (workspace)
               Real array, dimension (LWORK) On exit, if  INFO  =
               0, WORK(1) returns the optimal LWORK.

     LWORK (input)
               The dimension of the  array  WORK.   If  N  <=  1,
               LWORK  must  be at least 1.  If JOBZ = 'N' and N >
               1, LWORK must be at least 2*N.  If JOBZ = 'V'  and
               N > 1, LWORK must be at least 1 + 6*N + N**2.

               If LWORK = -1, then a workspace query is  assumed;
               the  routine  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 LWORK is issued by XERBLA.

     IWORK (workspace/output)
               Integer array, dimension (LIWORK) On exit, if INFO
               = 0, IWORK(1) returns the optimal LIWORK.

     LIWORK (input)
               The dimension of the array IWORK.  If JOBZ  =  'N'
               or  N <= 1, LIWORK must be at least 1.  If JOBZ  =
               'V' and N > 1, LIWORK must be at least 3 + 5*N.

               If LIWORK = -1, then a workspace query is assumed;
               the  routine  only  calculates the optimal size of
               the IWORK array, returns this value as  the  first
               entry  of  the  IWORK  array, and no error message
               related to LIWORK is issued by XERBLA.
     INFO (output)
               = 0:  successful exit
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value.
               > 0:  if INFO = i, the algorithm  failed  to  con-
               verge;  i off-diagonal elements of an intermediate
               tridiagonal form did not converge to zero.