dspev - compute all the eigenvalues and, optionally, eigenvectors of a real symmetric matrix A in packed storage
SUBROUTINE DSPEV(JOBZ, UPLO, N, AP, W, Z, LDZ, WORK, INFO) CHARACTER*1 JOBZ, UPLO INTEGER N, LDZ, INFO DOUBLE PRECISION AP(*), W(*), Z(LDZ,*), WORK(*) SUBROUTINE DSPEV_64(JOBZ, UPLO, N, AP, W, Z, LDZ, WORK, INFO) CHARACTER*1 JOBZ, UPLO INTEGER*8 N, LDZ, INFO DOUBLE PRECISION AP(*), W(*), Z(LDZ,*), WORK(*) F95 INTERFACE SUBROUTINE SPEV(JOBZ, UPLO, N, AP, W, Z, LDZ, WORK, INFO) CHARACTER(LEN=1) :: JOBZ, UPLO INTEGER :: N, LDZ, INFO REAL(8), DIMENSION(:) :: AP, W, WORK REAL(8), DIMENSION(:,:) :: Z SUBROUTINE SPEV_64(JOBZ, UPLO, N, AP, W, Z, LDZ, WORK, INFO) CHARACTER(LEN=1) :: JOBZ, UPLO INTEGER(8) :: N, LDZ, INFO REAL(8), DIMENSION(:) :: AP, W, WORK REAL(8), DIMENSION(:,:) :: Z C INTERFACE #include <sunperf.h> void dspev(char jobz, char uplo, int n, double *ap, double *w, double *z, int ldz, int *info); void dspev_64(char jobz, char uplo, long n, double *ap, double *w, dou- ble *z, long ldz, long *info);
Oracle Solaris Studio Performance Library dspev(3P)
NAME
dspev - compute all the eigenvalues and, optionally, eigenvectors of a
real symmetric matrix A in packed storage
SYNOPSIS
SUBROUTINE DSPEV(JOBZ, UPLO, N, AP, W, Z, LDZ, WORK, INFO)
CHARACTER*1 JOBZ, UPLO
INTEGER N, LDZ, INFO
DOUBLE PRECISION AP(*), W(*), Z(LDZ,*), WORK(*)
SUBROUTINE DSPEV_64(JOBZ, UPLO, N, AP, W, Z, LDZ, WORK, INFO)
CHARACTER*1 JOBZ, UPLO
INTEGER*8 N, LDZ, INFO
DOUBLE PRECISION AP(*), W(*), Z(LDZ,*), WORK(*)
F95 INTERFACE
SUBROUTINE SPEV(JOBZ, UPLO, N, AP, W, Z, LDZ, WORK, INFO)
CHARACTER(LEN=1) :: JOBZ, UPLO
INTEGER :: N, LDZ, INFO
REAL(8), DIMENSION(:) :: AP, W, WORK
REAL(8), DIMENSION(:,:) :: Z
SUBROUTINE SPEV_64(JOBZ, UPLO, N, AP, W, Z, LDZ, WORK, INFO)
CHARACTER(LEN=1) :: JOBZ, UPLO
INTEGER(8) :: N, LDZ, INFO
REAL(8), DIMENSION(:) :: AP, W, WORK
REAL(8), DIMENSION(:,:) :: Z
C INTERFACE
#include <sunperf.h>
void dspev(char jobz, char uplo, int n, double *ap, double *w, double
*z, int ldz, int *info);
void dspev_64(char jobz, char uplo, long n, double *ap, double *w, dou-
ble *z, long ldz, long *info);
PURPOSE
dspev computes all the eigenvalues and, optionally, eigenvectors of a
real symmetric matrix A in packed storage.
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 symmetric 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 diag-
onal and first subdiagonal of T overwrite the corresponding
elements of A.
W (output)
Double precision array, dimension (N) If INFO = 0, the eigen-
values in ascending order.
Z (output)
Double precision array, dimension (LDZ, N) If JOBZ = 'V',
then if INFO = 0, Z contains the orthonormal eigenvectors of
the matrix A, with the i-th column of Z holding the eigenvec-
tor associated with W(i). If JOBZ = 'N', then Z is not ref-
erenced.
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(3*N)
INFO (output)
= 0: successful exit.
< 0: if INFO = -i, the i-th argument had an illegal value.
> 0: if INFO = i, the algorithm failed to converge; i off-
diagonal elements of an intermediate tridiagonal form did not
converge to zero.
7 Nov 2015 dspev(3P)