Contents


NAME

     dpteqr - compute all eigenvalues and, optionally,  eigenvec-
     tors  of a symmetric positive definite tridiagonal matrix by
     first factoring the matrix using SPTTRF,  and  then  calling
     SBDSQR to compute the singular values of the bidiagonal fac-
     tor

SYNOPSIS

     SUBROUTINE DPTEQR(COMPZ, N, D, E, Z, LDZ, WORK, INFO)

     CHARACTER * 1 COMPZ
     INTEGER N, LDZ, INFO
     DOUBLE PRECISION D(*), E(*), Z(LDZ,*), WORK(*)

     SUBROUTINE DPTEQR_64(COMPZ, N, D, E, Z, LDZ, WORK, INFO)

     CHARACTER * 1 COMPZ
     INTEGER*8 N, LDZ, INFO
     DOUBLE PRECISION D(*), E(*), Z(LDZ,*), WORK(*)

  F95 INTERFACE
     SUBROUTINE PTEQR(COMPZ, [N], D, E, Z, [LDZ], [WORK], [INFO])

     CHARACTER(LEN=1) :: COMPZ
     INTEGER :: N, LDZ, INFO
     REAL(8), DIMENSION(:) :: D, E, WORK
     REAL(8), DIMENSION(:,:) :: Z

     SUBROUTINE PTEQR_64(COMPZ, [N], D, E, Z, [LDZ], [WORK], [INFO])

     CHARACTER(LEN=1) :: COMPZ
     INTEGER(8) :: N, LDZ, INFO
     REAL(8), DIMENSION(:) :: D, E, WORK
     REAL(8), DIMENSION(:,:) :: Z

  C INTERFACE
     #include <sunperf.h>

     void dpteqr(char compz, int n, double *d, double *e,  double
               *z, int ldz, int *info);

     void dpteqr_64(char compz, long n,  double  *d,  double  *e,
               double *z, long ldz, long *info);

PURPOSE

     dpteqr   computes   all   eigenvalues    and,    optionally,
     eigenvectors  of  a  symmetric positive definite tridiagonal
     matrix by first factoring the matrix using SPTTRF, and  then
     calling SBDSQR to compute the singular values of the bidiag-
     onal factor.

     This routine computes the eigenvalues of the positive defin-
     ite  tridiagonal  matrix  to  high  relative accuracy.  This
     means that if the eigenvalues range over many orders of mag-
     nitude in size, then the small eigenvalues and corresponding
     eigenvectors will be  computed  more  accurately  than,  for
     example, with the standard QR method.

     The eigenvectors of a full or band symmetric positive defin-
     ite  matrix  can  also be found if SSYTRD, SSPTRD, or SSBTRD
     has been used to reduce this  matrix  to  tridiagonal  form.
     (The  reduction  to  tridiagonal form, however, may preclude
     the possibility of obtaining high relative accuracy  in  the
     small  eigenvalues  of  the original matrix, if these eigen-
     values range over many orders of magnitude.)

ARGUMENTS

     COMPZ (input)
               = 'N':  Compute eigenvalues only.
               = 'V':  Compute eigenvectors of original symmetric
               matrix  also.   Array  Z  contains  the orthogonal
               matrix used to reduce the original matrix to  tri-
               diagonal  form.   =  'I':  Compute eigenvectors of
               tridiagonal matrix also.

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

     D (input/output)
               On entry, the n diagonal elements of the tridiago-
               nal matrix.  On normal exit, D contains the eigen-
               values, in descending order.

     E (input/output)
               On entry, the (n-1) subdiagonal  elements  of  the
               tridiagonal  matrix.   On  exit,  E  has been des-
               troyed.

     Z (input) On entry, if COMPZ = 'V',  the  orthogonal  matrix
               used  in  the  reduction  to tridiagonal form.  On
               exit, if COMPZ = 'V', the orthonormal eigenvectors
               of  the original symmetric matrix; if COMPZ = 'I',
               the orthonormal eigenvectors  of  the  tridiagonal
               matrix.   If  INFO  >  0  on  exit, Z contains the
               eigenvectors  associated  with  only  the   stored
               eigenvalues.   If   COMPZ  =  'N',  then  Z is not
               referenced.

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

     WORK (workspace)
               dimension(4*N)

     INFO (output)
               = 0:  successful exit.
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value.
               > 0:  if INFO = i, and i is:  <= N   the  Cholesky
               factorization of the matrix could not be performed
               because the i-th principal minor was not  positive
               definite.   > N   the SVD algorithm failed to con-
               verge; if INFO = N+i, i off-diagonal  elements  of
               the bidiagonal factor did not converge to zero.