Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dsyevd (3p)

Name

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

Synopsis

SUBROUTINE DSYEVD(JOBZ, UPLO, N, A, LDA, W, WORK, LWORK, IWORK,
LIWORK, INFO)

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

SUBROUTINE DSYEVD_64(JOBZ, UPLO, N, A, LDA, W, WORK, LWORK, IWORK,
LIWORK, INFO)

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




F95 INTERFACE
SUBROUTINE SYEVD(JOBZ, UPLO, N, A, LDA, W, WORK, LWORK, IWORK,
LIWORK, INFO)

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

SUBROUTINE SYEVD_64(JOBZ, UPLO, N, A, LDA, W, WORK, LWORK,
IWORK, LIWORK, INFO)

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




C INTERFACE
#include <sunperf.h>

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

void  dsyevd_64(char jobz, char uplo, long n, double *a, long lda, dou-
ble *w, long *info);

Description

Oracle Solaris Studio Performance Library                           dsyevd(3P)



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


SYNOPSIS
       SUBROUTINE DSYEVD(JOBZ, UPLO, N, A, LDA, W, WORK, LWORK, IWORK,
             LIWORK, INFO)

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

       SUBROUTINE DSYEVD_64(JOBZ, UPLO, N, A, LDA, W, WORK, LWORK, IWORK,
             LIWORK, INFO)

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




   F95 INTERFACE
       SUBROUTINE SYEVD(JOBZ, UPLO, N, A, LDA, W, WORK, LWORK, IWORK,
              LIWORK, INFO)

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

       SUBROUTINE SYEVD_64(JOBZ, UPLO, N, A, LDA, W, WORK, LWORK,
              IWORK, LIWORK, INFO)

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




   C INTERFACE
       #include <sunperf.h>

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

       void  dsyevd_64(char jobz, char uplo, long n, double *a, long lda, dou-
                 ble *w, long *info);



PURPOSE
       dsyevd computes all eigenvalues and, optionally, eigenvectors of a real
       symmetric  matrix  A. If eigenvectors are desired, it uses a divide and
       conquer algorithm.

       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  dig-
       its, but we know of none.

       Because  of  large  use  of  BLAS  of  level  3, DSYEVD needs N**2 more
       workspace than DSYEVX.


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)
                 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+1.  If JOBZ = 'V' and N > 1, LWORK must
                 be at least 1 + 6*N + 2*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)
                 On exit, if INFO = 0, IWORK(1) returns the optimal LIWORK.


       LIWORK (input)
                 The   dimension   of   the   array   IWORK.    If   N  <=  1,
                 LIWORK must be at least 1.  If JOBZ  = 'N' and 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  rou-
                 tine  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 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.

FURTHER DETAILS
       Based on contributions by
          Jeff Rutter, Computer Science Division, University of California
          at Berkeley, USA
       Modified by Francoise Tisseur, University of Tennessee.




                                  7 Nov 2015                        dsyevd(3P)