Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dsyev (3p)

Name

dsyev - compute all eigenvalues and, optionally, eigenvectors of a real symmetric matrix A

Synopsis

SUBROUTINE DSYEV(JOBZ, UPLO, N, A, LDA, W, WORK, LDWORK, INFO)

CHARACTER*1 JOBZ, UPLO
INTEGER N, LDA, LDWORK, INFO
DOUBLE PRECISION A(LDA,*), W(*), WORK(*)

SUBROUTINE DSYEV_64(JOBZ, UPLO, N, A, LDA, W, WORK, LDWORK, INFO)

CHARACTER*1 JOBZ, UPLO
INTEGER*8 N, LDA, LDWORK, INFO
DOUBLE PRECISION A(LDA,*), W(*), WORK(*)




F95 INTERFACE
SUBROUTINE SYEV(JOBZ, UPLO, N, A, LDA, W, WORK, LDWORK, INFO)

CHARACTER(LEN=1) :: JOBZ, UPLO
INTEGER :: N, LDA, LDWORK, INFO
REAL(8), DIMENSION(:) :: W, WORK
REAL(8), DIMENSION(:,:) :: A

SUBROUTINE SYEV_64(JOBZ, UPLO, N, A, LDA, W, WORK, LDWORK,
INFO)

CHARACTER(LEN=1) :: JOBZ, UPLO
INTEGER(8) :: N, LDA, LDWORK, INFO
REAL(8), DIMENSION(:) :: W, WORK
REAL(8), DIMENSION(:,:) :: A




C INTERFACE
#include <sunperf.h>

void dsyev(char jobz, char uplo, int n, double *a, int lda, double  *w,
int *info);

void dsyev_64(char jobz, char uplo, long n, double *a, long lda, double
*w, long *info);

Description

Oracle Solaris Studio Performance Library                            dsyev(3P)



NAME
       dsyev - compute all eigenvalues and, optionally, eigenvectors of a real
       symmetric matrix A


SYNOPSIS
       SUBROUTINE DSYEV(JOBZ, UPLO, N, A, LDA, W, WORK, LDWORK, INFO)

       CHARACTER*1 JOBZ, UPLO
       INTEGER N, LDA, LDWORK, INFO
       DOUBLE PRECISION A(LDA,*), W(*), WORK(*)

       SUBROUTINE DSYEV_64(JOBZ, UPLO, N, A, LDA, W, WORK, LDWORK, INFO)

       CHARACTER*1 JOBZ, UPLO
       INTEGER*8 N, LDA, LDWORK, INFO
       DOUBLE PRECISION A(LDA,*), W(*), WORK(*)




   F95 INTERFACE
       SUBROUTINE SYEV(JOBZ, UPLO, N, A, LDA, W, WORK, LDWORK, INFO)

       CHARACTER(LEN=1) :: JOBZ, UPLO
       INTEGER :: N, LDA, LDWORK, INFO
       REAL(8), DIMENSION(:) :: W, WORK
       REAL(8), DIMENSION(:,:) :: A

       SUBROUTINE SYEV_64(JOBZ, UPLO, N, A, LDA, W, WORK, LDWORK,
              INFO)

       CHARACTER(LEN=1) :: JOBZ, UPLO
       INTEGER(8) :: N, LDA, LDWORK, INFO
       REAL(8), DIMENSION(:) :: W, WORK
       REAL(8), DIMENSION(:,:) :: A




   C INTERFACE
       #include <sunperf.h>

       void dsyev(char jobz, char uplo, int n, double *a, int lda, double  *w,
                 int *info);

       void dsyev_64(char jobz, char uplo, long n, double *a, long lda, double
                 *w, long *info);



PURPOSE
       dsyev computes all eigenvalues and, optionally, eigenvectors of a  real
       symmetric matrix A.


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.


       A (input/output)
                 On entry, the symmetric 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, if JOBZ = 'V', then if INFO = 0, A
                 contains the orthonormal eigenvectors of the  matrix  A.   If
                 JOBZ  = 'N', then on exit the lower triangle (if UPLO='L') or
                 the upper triangle (if UPLO='U') of A, including  the  diago-
                 nal, is destroyed.


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


       W (output)
                 If INFO = 0, the eigenvalues in ascending order.


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


       LDWORK (input)
                 The  length  of the array WORK.  LDWORK >= max(1,3*N-1).  For
                 optimal efficiency, LDWORK  >=  (NB+2)*N,  where  NB  is  the
                 blocksize for DSYTRD 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.


       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                         dsyev(3P)