Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dhseqr (3p)

Name

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

Synopsis

SUBROUTINE DHSEQR(JOB, COMPZ, N, ILO, IHI, H, LDH, WR, WI, Z, LDZ,
WORK, LWORK, INFO)

CHARACTER*1 JOB, COMPZ
INTEGER N, ILO, IHI, LDH, LDZ, LWORK, INFO
DOUBLE PRECISION H(LDH,*), WR(*), WI(*), Z(LDZ,*), WORK(*)

SUBROUTINE DHSEQR_64(JOB, COMPZ, N, ILO, IHI, H, LDH, WR, WI, Z, LDZ,
WORK, LWORK, INFO)

CHARACTER*1 JOB, COMPZ
INTEGER*8 N, ILO, IHI, LDH, LDZ, LWORK, INFO
DOUBLE PRECISION H(LDH,*), WR(*), WI(*), Z(LDZ,*), WORK(*)




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

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

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

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




C INTERFACE
#include <sunperf.h>

void dhseqr(char job, char compz, int n, int ilo, int ihi,  double  *h,
int  ldh,  double  *wr,  double  *wi, double *z, int ldz, int
*info);

void dhseqr_64(char job, char compz, long n, long ilo, long ihi, double
*h,  long  ldh,  double *wr, double *wi, double *z, long ldz,
long *info);

Description

Oracle Solaris Studio Performance Library                           dhseqr(3P)



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


SYNOPSIS
       SUBROUTINE DHSEQR(JOB, COMPZ, N, ILO, IHI, H, LDH, WR, WI, Z, LDZ,
             WORK, LWORK, INFO)

       CHARACTER*1 JOB, COMPZ
       INTEGER N, ILO, IHI, LDH, LDZ, LWORK, INFO
       DOUBLE PRECISION H(LDH,*), WR(*), WI(*), Z(LDZ,*), WORK(*)

       SUBROUTINE DHSEQR_64(JOB, COMPZ, N, ILO, IHI, H, LDH, WR, WI, Z, LDZ,
             WORK, LWORK, INFO)

       CHARACTER*1 JOB, COMPZ
       INTEGER*8 N, ILO, IHI, LDH, LDZ, LWORK, INFO
       DOUBLE PRECISION H(LDH,*), WR(*), WI(*), Z(LDZ,*), WORK(*)




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

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

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

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




   C INTERFACE
       #include <sunperf.h>

       void dhseqr(char job, char compz, int n, int ilo, int ihi,  double  *h,
                 int  ldh,  double  *wr,  double  *wi, double *z, int ldz, int
                 *info);

       void dhseqr_64(char job, char compz, long n, long ilo, long ihi, double
                 *h,  long  ldh,  double *wr, double *wi, double *z, long ldz,
                 long *info);



PURPOSE
       dhseqr computes the eigenvalues of a real  upper  Hessenberg  matrix  H
       and,  optionally, the matrices T and Z from the Schur decomposition H =
       Z T Z**T, where T is an upper quasi-triangular matrix (the Schur form),
       and Z is the orthogonal matrix of Schur vectors.

       Optionally  Z  may be postmultiplied into an input orthogonal 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 orthogonal
       matrix Q:  A = Q*H*Q**T = (QZ)*T*(QZ)**T.


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
                 orthogonal  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 DGEBAL, and then passed to DGEHRD when the
                 matrix output by DGEBAL 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 quasi-triangular matrix T from the
                 Schur decomposition (the Schur form); 2-by-2 diagonal  blocks
                 (corresponding to complex conjugate pairs of eigenvalues) are
                 returned in standard  form,  with  H(i,i)  =  H(i+1,i+1)  and
                 H(i+1,i)*H(i,i+1)  <  0.  If JOB = 'E', the contents of H are
                 unspecified on exit.


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


       WR (output)
                 The real and imaginary parts, respectively, of  the  computed
                 eigenvalues.  If  two  eigenvalues  are computed as a complex
                 conjugate pair, they are stored in consecutive elements of WR
                 and  WI, say the i-th and (i+1)th, with WI(i) > 0 and WI(i+1)
                 < 0. If JOB = 'S', the eigenvalues are  stored  in  the  same
                 order  as  on  the  diagonal of the Schur form returned in H,
                 with WR(i) = H(i,i) and, if H(i:i+1,i:i+1) is a 2-by-2 diago-
                 nal  block,  WI(i)  =  sqrt(H(i+1,i)*H(i,i+1))  and WI(i+1) =
                 -WI(i).


       WI (output)
                 See the description of WR.


       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  orthogonal 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 orthogonal matrix generated by DORGHR after
                 the call to DGEHRD 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, DHSEQR failed to compute all of the eigen-
                 values  in  a  total  of  30*(IHI-ILO+1) iterations; elements
                 1:ilo-1 and i+1:n of WR  and  WI  contain  those  eigenvalues
                 which have been successfully computed.




                                  7 Nov 2015                        dhseqr(3P)