Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

chseqr (3p)

Name

chseqr - compute the eigenvalues of a complex upper Hessenberg matrix H, and, optionally, the matrices T and Z from the Schur decomposition H = Z T Z**H, where T is an upper triangular matrix (the Schur form), and Z is the unitary matrix of Schur vectors

Synopsis

SUBROUTINE CHSEQR(JOB, COMPZ, N, ILO, IHI, H, LDH, W, Z, LDZ, WORK,
LWORK, INFO)

CHARACTER*1 JOB, COMPZ
COMPLEX H(LDH,*), W(*), Z(LDZ,*), WORK(*)
INTEGER N, ILO, IHI, LDH, LDZ, LWORK, INFO

SUBROUTINE CHSEQR_64(JOB, COMPZ, N, ILO, IHI, H, LDH, W, Z, LDZ,
WORK, LWORK, INFO)

CHARACTER*1 JOB, COMPZ
COMPLEX H(LDH,*), W(*), Z(LDZ,*), WORK(*)
INTEGER*8 N, ILO, IHI, LDH, LDZ, LWORK, INFO




F95 INTERFACE
SUBROUTINE HSEQR(JOB, COMPZ, N, ILO, IHI, H, LDH, W, Z, LDZ,
WORK, LWORK, INFO)

CHARACTER(LEN=1) :: JOB, COMPZ
COMPLEX, DIMENSION(:) :: W, WORK
COMPLEX, DIMENSION(:,:) :: H, Z
INTEGER :: N, ILO, IHI, LDH, LDZ, LWORK, INFO

SUBROUTINE HSEQR_64(JOB, COMPZ, N, ILO, IHI, H, LDH, W, Z, LDZ,
WORK, LWORK, INFO)

CHARACTER(LEN=1) :: JOB, COMPZ
COMPLEX, DIMENSION(:) :: W, WORK
COMPLEX, DIMENSION(:,:) :: H, Z
INTEGER(8) :: N, ILO, IHI, LDH, LDZ, LWORK, INFO




C INTERFACE
#include <sunperf.h>

void chseqr (char job, char compz, int n, int ilo, int ihi, complex* h,
int ldh, complex* w, complex* z, int ldz, int* info);

void  chseqr_64 (char job, char compz, long n, long ilo, long ihi, com-
plex* h, long ldh, complex* w, complex* z,  long  ldz,  long*
info);

Description

Oracle Solaris Studio Performance Library                           chseqr(3P)



NAME
       chseqr  -  compute the eigenvalues of a complex upper Hessenberg matrix
       H, and, optionally, the matrices T and Z from the Schur decomposition H
       = Z T Z**H, where T is an upper triangular matrix (the Schur form), and
       Z is the unitary matrix of Schur vectors


SYNOPSIS
       SUBROUTINE CHSEQR(JOB, COMPZ, N, ILO, IHI, H, LDH, W, Z, LDZ, WORK,
             LWORK, INFO)

       CHARACTER*1 JOB, COMPZ
       COMPLEX H(LDH,*), W(*), Z(LDZ,*), WORK(*)
       INTEGER N, ILO, IHI, LDH, LDZ, LWORK, INFO

       SUBROUTINE CHSEQR_64(JOB, COMPZ, N, ILO, IHI, H, LDH, W, Z, LDZ,
             WORK, LWORK, INFO)

       CHARACTER*1 JOB, COMPZ
       COMPLEX H(LDH,*), W(*), Z(LDZ,*), WORK(*)
       INTEGER*8 N, ILO, IHI, LDH, LDZ, LWORK, INFO




   F95 INTERFACE
       SUBROUTINE HSEQR(JOB, COMPZ, N, ILO, IHI, H, LDH, W, Z, LDZ,
              WORK, LWORK, INFO)

       CHARACTER(LEN=1) :: JOB, COMPZ
       COMPLEX, DIMENSION(:) :: W, WORK
       COMPLEX, DIMENSION(:,:) :: H, Z
       INTEGER :: N, ILO, IHI, LDH, LDZ, LWORK, INFO

       SUBROUTINE HSEQR_64(JOB, COMPZ, N, ILO, IHI, H, LDH, W, Z, LDZ,
              WORK, LWORK, INFO)

       CHARACTER(LEN=1) :: JOB, COMPZ
       COMPLEX, DIMENSION(:) :: W, WORK
       COMPLEX, DIMENSION(:,:) :: H, Z
       INTEGER(8) :: N, ILO, IHI, LDH, LDZ, LWORK, INFO




   C INTERFACE
       #include <sunperf.h>

       void chseqr (char job, char compz, int n, int ilo, int ihi, complex* h,
                 int ldh, complex* w, complex* z, int ldz, int* info);

       void  chseqr_64 (char job, char compz, long n, long ilo, long ihi, com-
                 plex* h, long ldh, complex* w, complex* z,  long  ldz,  long*
                 info);



PURPOSE
       chseqr computes the eigenvalues of a complex upper Hessenberg matrix H,
       and, optionally, the matrices T and Z from the Schur decomposition H  =
       Z T Z**H, where T is an upper triangular matrix (the Schur form), and Z
       is the unitary matrix of Schur vectors.

       Optionally Z may be postmultiplied into an input unitary matrix  Q,  so
       that  this routine can give the Schur factorization of a matrix A which
       has been reduced to the Hessenberg form H by the unitary matrix Q:  A =
       Q*H*Q**H = (QZ)*T*(QZ)**H.


ARGUMENTS
       JOB (input)
                 = 'E': compute eigenvalues only;
                 = 'S': compute eigenvalues and the Schur form T.


       COMPZ (input)
                 = 'N': no Schur vectors are computed;
                 =  'I':  Z is initialized to the unit matrix and the matrix Z
                 of Schur vectors of H is returned; = 'V': Z must  contain  an
                 unitary matrix Q on entry, and the product Q*Z is returned.


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


       ILO (input)
                 It  is assumed that H is already upper triangular in rows and
                 columns 1:ILO-1 and IHI+1:N. ILO and IHI are normally set  by
                 a previous call to CGEBAL, and then passed to CGEHRD when the
                 matrix output by CGEBAL is reduced to Hessenberg form. Other-
                 wise ILO and IHI should be set to 1 and N respectively.  1 <=
                 ILO <= IHI <= N, if N > 0; ILO=1 and IHI=0, if N=0.


       IHI (input)
                 See the description of ILO.


       H (input/output)
                 On entry, the upper Hessenberg matrix H.  On exit, if  JOB  =
                 'S',  H contains the upper triangular matrix T from the Schur
                 decomposition (the Schur form). If JOB = 'E', the contents of
                 H are unspecified on exit.


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


       W (output)
                 The  computed  eigenvalues. If JOB = 'S', the eigenvalues are
                 stored in the same order as on the diagonal of the Schur form
                 returned in H, with W(i) = H(i,i).


       Z (input) If COMPZ = 'N': Z is not referenced.
                 If  COMPZ  = 'I': on entry, Z need not be set, and on exit, Z
                 contains the unitary matrix Z of the Schur vectors of H.   If
                 COMPZ  =  'V':  on  entry  Z must contain an N-by-N matrix Q,
                 which is assumed to be equal to the unit  matrix  except  for
                 the  submatrix  Z(ILO:IHI,ILO:IHI);  on  exit Z contains Q*Z.
                 Normally Q is the unitary matrix generated  by  CUNGHR  after
                 the call to CGEHRD which formed the Hessenberg matrix H.


       LDZ (input)
                 The  leading  dimension  of  the array Z.  LDZ >= max(1,N) if
                 COMPZ = 'I' or 'V'; LDZ >= 1 otherwise.


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


       LWORK (input)
                 The dimension of the array WORK.  LWORK >= max(1,N).

                 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.


       INFO (output)
                 = 0:  successful exit
                 < 0:  if INFO = -i, the i-th argument had an illegal value
                 > 0:  if INFO = i, CHSEQR failed to compute all the eigenval-
                 ues in a total of 30*(IHI-ILO+1) iterations; elements 1:ilo-1
                 and i+1:n of W contain those eigenvalues which have been suc-
                 cessfully computed.




                                  7 Nov 2015                        chseqr(3P)