Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

sstedc (3p)

Name

sstedc - compute all eigenvalues and, optionally, eigenvectors of a symmetric tridiagonal matrix using the divide and conquer method

Synopsis

SUBROUTINE SSTEDC(COMPZ, N, D, E, Z, LDZ, WORK, LWORK, IWORK, LIWORK,
INFO)

CHARACTER*1 COMPZ
INTEGER N, LDZ, LWORK, LIWORK, INFO
INTEGER IWORK(*)
REAL D(*), E(*), Z(LDZ,*), WORK(*)

SUBROUTINE SSTEDC_64(COMPZ, N, D, E, Z, LDZ, WORK, LWORK, IWORK,
LIWORK, INFO)

CHARACTER*1 COMPZ
INTEGER*8 N, LDZ, LWORK, LIWORK, INFO
INTEGER*8 IWORK(*)
REAL D(*), E(*), Z(LDZ,*), WORK(*)




F95 INTERFACE
SUBROUTINE STEDC(COMPZ, N, D, E, Z, LDZ, WORK, LWORK, IWORK,
LIWORK, INFO)

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

SUBROUTINE STEDC_64(COMPZ, N, D, E, Z, LDZ, WORK, LWORK, IWORK,
LIWORK, INFO)

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




C INTERFACE
#include <sunperf.h>

void sstedc(char compz, int n, float *d, float *e, float *z,  int  ldz,
int *info);

void  sstedc_64(char  compz, long n, float *d, float *e, float *z, long
ldz, long *info);

Description

Oracle Solaris Studio Performance Library                           sstedc(3P)



NAME
       sstedc  -  compute  all  eigenvalues and, optionally, eigenvectors of a
       symmetric tridiagonal matrix using the divide and conquer method


SYNOPSIS
       SUBROUTINE SSTEDC(COMPZ, N, D, E, Z, LDZ, WORK, LWORK, IWORK, LIWORK,
             INFO)

       CHARACTER*1 COMPZ
       INTEGER N, LDZ, LWORK, LIWORK, INFO
       INTEGER IWORK(*)
       REAL D(*), E(*), Z(LDZ,*), WORK(*)

       SUBROUTINE SSTEDC_64(COMPZ, N, D, E, Z, LDZ, WORK, LWORK, IWORK,
             LIWORK, INFO)

       CHARACTER*1 COMPZ
       INTEGER*8 N, LDZ, LWORK, LIWORK, INFO
       INTEGER*8 IWORK(*)
       REAL D(*), E(*), Z(LDZ,*), WORK(*)




   F95 INTERFACE
       SUBROUTINE STEDC(COMPZ, N, D, E, Z, LDZ, WORK, LWORK, IWORK,
              LIWORK, INFO)

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

       SUBROUTINE STEDC_64(COMPZ, N, D, E, Z, LDZ, WORK, LWORK, IWORK,
              LIWORK, INFO)

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




   C INTERFACE
       #include <sunperf.h>

       void sstedc(char compz, int n, float *d, float *e, float *z,  int  ldz,
                 int *info);

       void  sstedc_64(char  compz, long n, float *d, float *e, float *z, long
                 ldz, long *info);



PURPOSE
       sstedc computes all eigenvalues and, optionally, eigenvectors of a sym-
       metric  tridiagonal  matrix  using  the divide and conquer method.  The
       eigenvectors of a full or band real symmetric matrix can also be  found
       if  SSYTRD  or  SSPTRD or SSBTRD has been used to reduce this matrix to
       tridiagonal form.

       This code 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.  See SLAED3 for details.


ARGUMENTS
       COMPZ (input)
                 = 'N':  Compute eigenvalues only.
                 = 'I':  Compute eigenvectors of tridiagonal matrix also.
                 =  'V':   Compute  eigenvectors  of  original dense symmetric
                 matrix also.  On entry, Z contains the orthogonal matrix used
                 to reduce the original matrix to tridiagonal form.


       N (input) The dimension of the symmetric tridiagonal matrix.  N >= 0.


       D (input/output)
                 On  entry,  the  diagonal elements of the tridiagonal matrix.
                 On exit, if INFO = 0, the eigenvalues in ascending order.


       E (input/output)
                 On entry, the subdiagonal elements of the tridiagonal matrix.
                 On exit, E has been destroyed.


       Z (input) On  entry,  if  COMPZ  =  'V', then Z contains the orthogonal
                 matrix used in the reduction to tridiagonal form.   On  exit,
                 if  INFO = 0, then if COMPZ = 'V', Z contains the orthonormal
                 eigenvectors of the original symmetric matrix, and if COMPZ =
                 'I', Z contains the orthonormal eigenvectors of the symmetric
                 tridiagonal matrix.  If  COMPZ = 'N', then Z  is  not  refer-
                 enced.


       LDZ (input)
                 The  leading  dimension of the array Z.  LDZ >= 1.  If eigen-
                 vectors are desired, then LDZ >= max(1,N).


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


       LWORK (input)
                 The  dimension  of  the array WORK.  If COMPZ = 'N' or N <= 1
                 then LWORK must be at least 1.  If COMPZ = 'V' and N > 1 then
                 LWORK must be at least ( 1 + 3*N + 2*N*lg N + 4*N**2 ), where
                 lg( N ) = smallest integer k such that 2**k >= N.  If COMPZ =
                 'I' and N > 1 then LWORK must be at least ( 1 + 4*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)
                 On exit, if INFO = 0, IWORK(1) returns the optimal LIWORK.


       LIWORK (input)
                 The  dimension  of the array IWORK.  If COMPZ = 'N' or N <= 1
                 then LIWORK must be at least 1.  If COMPZ = 'V'  and  N  >  1
                 then  LIWORK  must  be  at  least ( 6 + 6*N + 5*N*lg N ).  If
                 COMPZ = 'I' and N > 1 then 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:  The algorithm failed to  compute  an  eigenvalue  while
                 working on the submatrix lying in rows and columns INFO/(N+1)
                 through mod(INFO,N+1).

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