Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

chsein (3p)

Name

chsein - use inverse iteration to find specified right and/or left eigenvectors of a complex upper Hessenberg matrix H

Synopsis

SUBROUTINE CHSEIN(SIDE, EIGSRC, INITV, SELECT, N, H, LDH, W, VL,
LDVL, VR, LDVR, MM, M, WORK, RWORK, IFAILL, IFAILR, INFO)

CHARACTER*1 SIDE, EIGSRC, INITV
COMPLEX H(LDH,*), W(*), VL(LDVL,*), VR(LDVR,*), WORK(*)
INTEGER N, LDH, LDVL, LDVR, MM, M, INFO
INTEGER IFAILL(*), IFAILR(*)
LOGICAL SELECT(*)
REAL RWORK(*)

SUBROUTINE CHSEIN_64(SIDE, EIGSRC, INITV, SELECT, N, H, LDH, W, VL,
LDVL, VR, LDVR, MM, M, WORK, RWORK, IFAILL, IFAILR, INFO)

CHARACTER*1 SIDE, EIGSRC, INITV
COMPLEX H(LDH,*), W(*), VL(LDVL,*), VR(LDVR,*), WORK(*)
INTEGER*8 N, LDH, LDVL, LDVR, MM, M, INFO
INTEGER*8 IFAILL(*), IFAILR(*)
LOGICAL*8 SELECT(*)
REAL RWORK(*)




F95 INTERFACE
SUBROUTINE HSEIN(SIDE, EIGSRC, INITV, SELECT, N, H, LDH, W, VL,
LDVL, VR, LDVR, MM, M, WORK, RWORK, IFAILL, IFAILR, INFO)

CHARACTER(LEN=1) :: SIDE, EIGSRC, INITV
COMPLEX, DIMENSION(:) :: W, WORK
COMPLEX, DIMENSION(:,:) :: H, VL, VR
INTEGER :: N, LDH, LDVL, LDVR, MM, M, INFO
INTEGER, DIMENSION(:) :: IFAILL, IFAILR
LOGICAL, DIMENSION(:) :: SELECT
REAL, DIMENSION(:) :: RWORK

SUBROUTINE HSEIN_64(SIDE, EIGSRC, INITV, SELECT, N, H, LDH, W,
VL, LDVL, VR, LDVR, MM, M, WORK, RWORK, IFAILL, IFAILR,
INFO)

CHARACTER(LEN=1) :: SIDE, EIGSRC, INITV
COMPLEX, DIMENSION(:) :: W, WORK
COMPLEX, DIMENSION(:,:) :: H, VL, VR
INTEGER(8) :: N, LDH, LDVL, LDVR, MM, M, INFO
INTEGER(8), DIMENSION(:) :: IFAILL, IFAILR
LOGICAL(8), DIMENSION(:) :: SELECT
REAL, DIMENSION(:) :: RWORK




C INTERFACE
#include <sunperf.h>

void chsein(char side, char eigsrc, char initv,  int  *select,  int  n,
complex  *h, int ldh, complex *w, complex *vl, int ldvl, com-
plex *vr, int ldvr, int mm, int *m, int *ifaill, int *ifailr,
int *info);

void  chsein_64(char  side, char eigsrc, char initv, long *select, long
n, complex *h, long ldh, complex *w, complex *vl, long  ldvl,
complex  *vr, long ldvr, long mm, long *m, long *ifaill, long
*ifailr, long *info);

Description

Oracle Solaris Studio Performance Library                           chsein(3P)



NAME
       chsein  -  use  inverse  iteration  to find specified right and/or left
       eigenvectors of a complex upper Hessenberg matrix H


SYNOPSIS
       SUBROUTINE CHSEIN(SIDE, EIGSRC, INITV, SELECT, N, H, LDH, W, VL,
             LDVL, VR, LDVR, MM, M, WORK, RWORK, IFAILL, IFAILR, INFO)

       CHARACTER*1 SIDE, EIGSRC, INITV
       COMPLEX H(LDH,*), W(*), VL(LDVL,*), VR(LDVR,*), WORK(*)
       INTEGER N, LDH, LDVL, LDVR, MM, M, INFO
       INTEGER IFAILL(*), IFAILR(*)
       LOGICAL SELECT(*)
       REAL RWORK(*)

       SUBROUTINE CHSEIN_64(SIDE, EIGSRC, INITV, SELECT, N, H, LDH, W, VL,
             LDVL, VR, LDVR, MM, M, WORK, RWORK, IFAILL, IFAILR, INFO)

       CHARACTER*1 SIDE, EIGSRC, INITV
       COMPLEX H(LDH,*), W(*), VL(LDVL,*), VR(LDVR,*), WORK(*)
       INTEGER*8 N, LDH, LDVL, LDVR, MM, M, INFO
       INTEGER*8 IFAILL(*), IFAILR(*)
       LOGICAL*8 SELECT(*)
       REAL RWORK(*)




   F95 INTERFACE
       SUBROUTINE HSEIN(SIDE, EIGSRC, INITV, SELECT, N, H, LDH, W, VL,
              LDVL, VR, LDVR, MM, M, WORK, RWORK, IFAILL, IFAILR, INFO)

       CHARACTER(LEN=1) :: SIDE, EIGSRC, INITV
       COMPLEX, DIMENSION(:) :: W, WORK
       COMPLEX, DIMENSION(:,:) :: H, VL, VR
       INTEGER :: N, LDH, LDVL, LDVR, MM, M, INFO
       INTEGER, DIMENSION(:) :: IFAILL, IFAILR
       LOGICAL, DIMENSION(:) :: SELECT
       REAL, DIMENSION(:) :: RWORK

       SUBROUTINE HSEIN_64(SIDE, EIGSRC, INITV, SELECT, N, H, LDH, W,
              VL, LDVL, VR, LDVR, MM, M, WORK, RWORK, IFAILL, IFAILR,
              INFO)

       CHARACTER(LEN=1) :: SIDE, EIGSRC, INITV
       COMPLEX, DIMENSION(:) :: W, WORK
       COMPLEX, DIMENSION(:,:) :: H, VL, VR
       INTEGER(8) :: N, LDH, LDVL, LDVR, MM, M, INFO
       INTEGER(8), DIMENSION(:) :: IFAILL, IFAILR
       LOGICAL(8), DIMENSION(:) :: SELECT
       REAL, DIMENSION(:) :: RWORK




   C INTERFACE
       #include <sunperf.h>

       void chsein(char side, char eigsrc, char initv,  int  *select,  int  n,
                 complex  *h, int ldh, complex *w, complex *vl, int ldvl, com-
                 plex *vr, int ldvr, int mm, int *m, int *ifaill, int *ifailr,
                 int *info);

       void  chsein_64(char  side, char eigsrc, char initv, long *select, long
                 n, complex *h, long ldh, complex *w, complex *vl, long  ldvl,
                 complex  *vr, long ldvr, long mm, long *m, long *ifaill, long
                 *ifailr, long *info);



PURPOSE
       chsein uses inverse iteration  to  find  specified  right  and/or  left
       eigenvectors of a complex upper Hessenberg matrix H.

       The right eigenvector x and the left eigenvector y of the matrix H cor-
       responding to an eigenvalue w are defined by:

                    H * x = w * x,     y**h * H = w * y**h

       where y**h denotes the conjugate transpose of the vector y.


ARGUMENTS
       SIDE (input)
                 = 'R': compute right eigenvectors only;
                 = 'L': compute left eigenvectors only;
                 = 'B': compute both right and left eigenvectors.


       EIGSRC (input)
                 Specifies the source of eigenvalues supplied in W:
                 = 'Q': the eigenvalues were found using CHSEQR;  thus,  if  H
                 has  zero  subdiagonal  elements, and so is block-triangular,
                 then the j-th eigenvalue can be assumed to be  an  eigenvalue
                 of  the  block containing the j-th row/column.  This property
                 allows CHSEIN to perform inverse iteration on just one diago-
                 nal  block.  = 'N': no assumptions are made on the correspon-
                 dence between eigenvalues and diagonal blocks.  In this case,
                 CHSEIN  must always perform inverse iteration using the whole
                 matrix H.


       INITV (input)
                 = 'N': no initial vectors are supplied;
                 = 'U': user-supplied initial vectors are stored in the arrays
                 VL and/or VR.


       SELECT (input)
                 Specifies  the  eigenvectors  to  be  computed. To select the
                 eigenvector corresponding to the eigenvalue  W(j),  SELECT(j)
                 must be set to .TRUE..


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


       H (input) The upper Hessenberg matrix H.


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


       W (input/output)
                 On entry, the eigenvalues of H.  On exit, the real parts of W
                 may have been altered since close eigenvalues  are  perturbed
                 slightly in searching for independent eigenvectors.


       VL (input/output)
                 On  entry, if INITV = 'U' and SIDE = 'L' or 'B', VL must con-
                 tain starting vectors for the inverse iteration for the  left
                 eigenvectors;  the  starting vector for each eigenvector must
                 be in the same  column  in  which  the  eigenvector  will  be
                 stored.  On exit, if SIDE = 'L' or 'B', the left eigenvectors
                 specified by SELECT will be stored consecutively in the  col-
                 umns  of VL, in the same order as their eigenvalues.  If SIDE
                 = 'R', VL is not referenced.


       LDVL (input)
                 The leading dimension of the array VL.  LDVL >=  max(1,N)  if
                 SIDE = 'L' or 'B'; LDVL >= 1 otherwise.


       VR (input/output)
                 On  entry, if INITV = 'U' and SIDE = 'R' or 'B', VR must con-
                 tain starting vectors for the inverse iteration for the right
                 eigenvectors;  the  starting vector for each eigenvector must
                 be in the same  column  in  which  the  eigenvector  will  be
                 stored.   On  exit, if SIDE = 'R' or 'B', the right eigenvec-
                 tors specified by SELECT will be stored consecutively in  the
                 columns  of  VR,  in the same order as their eigenvalues.  If
                 SIDE = 'L', VR is not referenced.


       LDVR (input)
                 The leading dimension of the array VR.  LDVR >=  max(1,N)  if
                 SIDE = 'R' or 'B'; LDVR >= 1 otherwise.


       MM (input)
                 The number of columns in the arrays VL and/or VR. MM >= M.


       M (output)
                 The  number of columns in the arrays VL and/or VR required to
                 store the eigenvectors (= the number of  .TRUE.  elements  in
                 SELECT).


       WORK (workspace)
                 dimension(N*N)

       RWORK (workspace)
                 dimension(N)

       IFAILL (output) INTEGER array, dimension (MM)
                 If SIDE = 'L' or 'B', IFAILL(i) = j > 0 if the left eigenvec-
                 tor in the i-th column of VL (corresponding to the eigenvalue
                 w(j))  failed  to  converge; IFAILL(i) = 0 if the eigenvector
                 converged satisfactorily.  If SIDE = 'R', IFAILL is not  ref-
                 erenced.


       IFAILR (output) INTEGER array, dimension (MM)
                 If  SIDE  = 'R' or 'B', IFAILR(i) = j > 0 if the right eigen-
                 vector in the i-th column of VR (corresponding to the  eigen-
                 value  w(j))  failed to converge; IFAILR(i) = 0 if the eigen-
                 vector converged satisfactorily.  If SIDE =  'L',  IFAILR  is
                 not referenced.


       INFO (output)
                 = 0:  successful exit
                 < 0:  if INFO = -i, the i-th argument had an illegal value
                 >  0:   if  INFO  =  i, i is the number of eigenvectors which
                 failed  to  converge;  see  IFAILL  and  IFAILR  for  further
                 details.

FURTHER DETAILS
       Each eigenvector is normalized so that the element of largest magnitude
       has magnitude 1; here the magnitude of a complex number (x,y) is  taken
       to be |x|+|y|.




                                  7 Nov 2015                        chsein(3P)