Contents


NAME

     cstein - compute the eigenvectors of a real symmetric tridi-
     agonal  matrix  T  corresponding  to  specified eigenvalues,
     using inverse iteration

SYNOPSIS

     SUBROUTINE CSTEIN(N, D, E, M, W, IBLOCK, ISPLIT, Z, LDZ, WORK, IWORK,
           IFAIL, INFO)

     COMPLEX Z(LDZ,*)
     INTEGER N, M, LDZ, INFO
     INTEGER IBLOCK(*), ISPLIT(*), IWORK(*), IFAIL(*)
     REAL D(*), E(*), W(*), WORK(*)

     SUBROUTINE CSTEIN_64(N, D, E, M, W, IBLOCK, ISPLIT, Z, LDZ, WORK,
           IWORK, IFAIL, INFO)

     COMPLEX Z(LDZ,*)
     INTEGER*8 N, M, LDZ, INFO
     INTEGER*8 IBLOCK(*), ISPLIT(*), IWORK(*), IFAIL(*)
     REAL D(*), E(*), W(*), WORK(*)

  F95 INTERFACE
     SUBROUTINE STEIN([N], D, E, [M], W, IBLOCK, ISPLIT, Z, [LDZ], [WORK],
            [IWORK], IFAIL, [INFO])

     COMPLEX, DIMENSION(:,:) :: Z
     INTEGER :: N, M, LDZ, INFO
     INTEGER, DIMENSION(:) :: IBLOCK, ISPLIT, IWORK, IFAIL
     REAL, DIMENSION(:) :: D, E, W, WORK

     SUBROUTINE STEIN_64([N], D, E, [M], W, IBLOCK, ISPLIT, Z, [LDZ],
            [WORK], [IWORK], IFAIL, [INFO])

     COMPLEX, DIMENSION(:,:) :: Z
     INTEGER(8) :: N, M, LDZ, INFO
     INTEGER(8), DIMENSION(:) :: IBLOCK, ISPLIT, IWORK, IFAIL
     REAL, DIMENSION(:) :: D, E, W, WORK

  C INTERFACE
     #include <sunperf.h>

     void cstein(int n, float *d, float *e, int m, float *w,  int
               *iblock,  int  *isplit,  complex  *z, int ldz, int
               *ifail, int *info);
     void cstein_64(long n, float *d, float *e, long m, float *w,
               long  *iblock, long *isplit, complex *z, long ldz,
               long *ifail, long *info);

PURPOSE

     cstein computes the eigenvectors of a real symmetric  tridi-
     agonal  matrix  T  corresponding  to  specified eigenvalues,
     using inverse iteration.

     The maximum number of iterations allowed for each  eigenvec-
     tor  is specified by an internal parameter MAXITS (currently
     set to 5).

     Although the eigenvectors are real, they  are  stored  in  a
     complex  array,  which may be passed to CUNMTR or CUPMTR for
     back
     transformation to the eigenvectors of  a  complex  Hermitian
     matrix which was reduced to tridiagonal form.

ARGUMENTS

     N (input) The order of the matrix.  N >= 0.

     D (input) The n diagonal elements of the tridiagonal  matrix
               T.

     E (input) The (n-1) subdiagonal elements of the  tridiagonal
               matrix  T,  stored in elements 1 to N-1; E(N) need
               not be set.

     M (input) The number of eigenvectors to be found.  0 <= M <=
               N.

     W (input) The first M elements of W contain the  eigenvalues
               for  which  eigenvectors  are to be computed.  The
               eigenvalues should be grouped by  split-off  block
               and  ordered  from  smallest to largest within the
               block.  ( The output  array  W  from  SSTEBZ  with
               ORDER = 'B' is expected here. )

     IBLOCK (input)
               The  submatrix   indices   associated   with   the
               corresponding  eigenvalues  in  W;  IBLOCK(i)=1 if
               eigenvalue W(i) belongs  to  the  first  submatrix
               from  the  top,  =2  if W(i) belongs to the second
               submatrix, etc.  ( The output  array  IBLOCK  from
               SSTEBZ is expected here. )

     ISPLIT (input)
               The splitting points, at which T  breaks  up  into
               submatrices.   The  first  submatrix  consists  of
               rows/columns 1 to  ISPLIT(  1  ),  the  second  of
               rows/columns  ISPLIT(  1  )+1 through ISPLIT( 2 ),
               etc.  ( The output array  ISPLIT  from  SSTEBZ  is
               expected here. )

     Z (output)
               The computed eigenvectors.  The eigenvector  asso-
               ciated  with  the eigenvalue W(i) is stored in the
               i-th column of Z.  Any vector which fails to  con-
               verge  is  set to its current iterate after MAXITS
               iterations.  The imaginary parts of the  eigenvec-
               tors are set to zero.

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

     WORK (workspace)
               dimension(5*N)

     IWORK (workspace)
               dimension(N)

     IFAIL (output)
               On normal exit, all elements of  IFAIL  are  zero.
               If one or more eigenvectors fail to converge after
               MAXITS iterations, then their indices  are  stored
               in array IFAIL.

     INFO (output)
               = 0: successful exit
               < 0: if INFO = -i, the i-th argument had an  ille-
               gal value
               > 0: if INFO = i, then i  eigenvectors  failed  to
               converge  in MAXITS iterations.  Their indices are
               stored in array IFAIL.