Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

csteqr (3p)

Name

csteqr - compute all eigenvalues and, optionally, eigenvectors of a symmetric tridiagonal matrix using the implicit QL or QR method

Synopsis

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

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

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

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




F95 INTERFACE
SUBROUTINE STEQR(COMPZ, N, D, E, Z, LDZ, WORK, INFO)

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

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

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




C INTERFACE
#include <sunperf.h>

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

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

Description

Oracle Solaris Studio Performance Library                           csteqr(3P)



NAME
       csteqr  -  compute  all  eigenvalues and, optionally, eigenvectors of a
       symmetric tridiagonal matrix using the implicit QL or QR method


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

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

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

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




   F95 INTERFACE
       SUBROUTINE STEQR(COMPZ, N, D, E, Z, LDZ, WORK, INFO)

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

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

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




   C INTERFACE
       #include <sunperf.h>

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

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



PURPOSE
       csteqr computes all eigenvalues and, optionally, eigenvectors of a sym-
       metric  tridiagonal  matrix  using  the  implicit QL or QR method.  The
       eigenvectors of a full or band complex Hermitian  matrix  can  also  be
       found if CHETRD or CHPTRD or CHBTRD has been used to reduce this matrix
       to tridiagonal form.


ARGUMENTS
       COMPZ (input)
                 = 'N':  Compute eigenvalues only.
                 = 'V':  Compute eigenvalues and eigenvectors of the  original
                 Hermitian  matrix.   On  entry,  Z  must  contain the unitary
                 matrix used to reduce  the  original  matrix  to  tridiagonal
                 form.   =  'I':   Compute eigenvalues and eigenvectors of the
                 tridiagonal matrix.  Z is initialized to the identity matrix.


       N (input) The order of the 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 (n-1) subdiagonal elements of  the  tridiagonal
                 matrix.  On exit, E has been destroyed.


       Z (input) On entry, if  COMPZ = 'V', then Z contains the unitary matrix
                 used in the reduction to tridiagonal form.  On exit, if  INFO
                 =  0,  then if COMPZ = 'V', Z contains the orthonormal eigen-
                 vectors of the original Hermitian 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, and if
                 eigenvectors are desired, then  LDZ >= max(1,N).


       WORK (workspace)
                 dimension(max(1,2*N-2)) If COMPZ = 'N', then WORK is not ref-
                 erenced.


       INFO (output)
                 = 0:  successful exit
                 < 0:  if INFO = -i, the i-th argument had an illegal value
                 > 0:  the algorithm has failed to find all the eigenvalues in
                 a total of 30*N iterations; if INFO = i, then i elements of E
                 have not converged to zero; on exit, D and E contain the ele-
                 ments of a symmetric tridiagonal matrix  which  is  unitarily
                 similar to the original matrix.




                                  7 Nov 2015                        csteqr(3P)