Previous: dhgeqz Up: ../lapack-d.html Next: dhseqr


dhsein


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

 SYNOPSIS
      SUBROUTINE DHSEIN( JOB, EIGSRC, INITV, SELECT, N, H, LDH,
                         WR, WI, VL, LDVL, VR, LDVR, MM, M, WORK,
                         IFAILL, IFAILR, INFO )

          CHARACTER      EIGSRC, INITV, JOB

          INTEGER        INFO, LDH, LDVL, LDVR, M, MM, N

          LOGICAL        SELECT( * )

          INTEGER        IFAILL( * ), IFAILR( * )

          DOUBLE         PRECISION H( LDH, * ), VL( LDVL, * ), VR(
                         LDVR, * ), WI( * ), WORK( * ), WR( * )

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

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

                   H x = w x,     y' H = w y'

      where y' denotes the conjugate transpose of the vector y.

 ARGUMENTS
      JOB     (input) CHARACTER*1
              = 'R': compute right eigenvectors only;
              = 'L': compute left eigenvectors only;
              = 'B': compute both right and left eigenvectors.

      EIGSRC  (input) CHARACTER*1
              Specifies the source of eigenvalues supplied in
              (WR,WI):
              = 'Q': the eigenvalues were found using DHSEQR;
              thus, if H has zero subdiagonal entries, 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 DHSEIN to
              perform inverse iteration on just one diagonal
              block.  = 'N': no assumptions are made on the
              correspondence between eigenvalues and diagonal
              blocks.  In this case, DHSEIN must always perform
              inverse iteration using the whole matrix H.

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

      SELECT  (input/output) LOGICAL array, dimension(N)
              Specifies the eigenvectors to be computed. To select
              the real eigenvector corresponding to a real eigen-
              value WR(j), SELECT(j) must be set to .TRUE.. To
              select the complex eigenvector corresponding to a
              complex eigenvalue (WR(j),WI(j)), with complex con-
              jugate (WR(j+1),WI(j+1)), either SELECT(j) or
              SELECT(j+1) or both must be set to .TRUE.; then on
              exit SELECT(j) is .TRUE. and SELECT(j+1) is .FALSE..

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

      H       (input) DOUBLE PRECISION array, dimension (LDH,N)
              The upper Hessenberg matrix H.

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

      WR      (input/output) DOUBLE PRECISION array, dimension (N)
              WI      (input) DOUBLE PRECISION array, dimension
              (N) On entry, the real and imaginary parts of the
              eigenvalues of H; a complex conjugate pair of eigen-
              values must be stored in consecutive elements of WR
              and WI.  On exit, WR may have been altered since
              close eigenvalues are perturbed slightly in search-
              ing for independent eigenvectors.

 (LDVL,MM)
      VL      (input/output) DOUBLE PRECISION array, dimension
              On entry, if INITV = 'U' and JOB = 'L' or 'B', VL
              must contain starting vectors for the inverse itera-
              tion for the left eigenvectors; the starting vector
              for each eigenvector must be in the same column(s)
              in which the eigenvector will be stored.  On exit,
              if JOB = 'L' or 'B', the left eigenvectors specified
              by SELECT will be stored consecutively in the
              columns of VL, in the same order as their eigen-
              values. A complex eigenvector corresponding to a
              complex eigenvalue is stored in two consecutive
              columns, the first holding the real part and the
              second the imaginary part.  If JOB = 'R', VL is not
              referenced.

      LDVL    (input) INTEGER
              The leading dimension of the array VL.  LDVL >=

              max(1,N) if JOB = 'L' or 'B'; LDVL >= 1 otherwise.

 (LDVR,MM)
      VR      (input/output) DOUBLE PRECISION array, dimension
              On entry, if INITV = 'U' and JOB = 'R' or 'B', VR
              must contain starting vectors for the inverse itera-
              tion for the right eigenvectors; the starting vector
              for each eigenvector must be in the same column(s)
              in which the eigenvector will be stored.  On exit,
              if JOB = 'R' or 'B', the right eigenvectors speci-
              fied by SELECT will be stored consecutively in the
              columns of VR, in the same order as their eigen-
              values. A complex eigenvector corresponding to a
              complex eigenvalue is stored in two consecutive
              columns, the first holding the real part and the
              second the imaginary part.  If JOB = 'L', VR is not
              referenced.

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

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

      M       (output) INTEGER
              The number of columns in the arrays VL and/or VR
              required to store the eigenvectors; each selected
              real eigenvector occupies one column and each
              selected complex eigenvector occupies two columns.

      WORK    (workspace) DOUBLE PRECISION array, dimension ((N+2)*N)

      IFAILL  (output) INTEGER array, dimension (MM)
              If JOB = 'L' or 'B', IFAILL(i) = j > 0 if the left
              eigenvector in the i-th column of VL (corresponding
              to the eigenvalue w(j)) failed to converge;
              IFAILL(i) = 0 if the eigenvector converged satisfac-
              torily. If the i-th and (i+1)th columns of VL hold a
              complex eigenvector, then IFAILL(i) and IFAILL(i+1)
              are set to the same value.  If JOB = 'R', IFAILL is
              not referenced.

      IFAILR  (output) INTEGER array, dimension (MM)
              If JOB = 'R' or 'B', IFAILR(i) = j > 0 if the right
              eigenvector in the i-th column of VR (corresponding
              to the eigenvalue w(j)) failed to converge;
              IFAILR(i) = 0 if the eigenvector converged satisfac-
              torily. If the i-th and (i+1)th columns of VR hold a
              complex eigenvector, then IFAILR(i) and IFAILR(i+1)
              are set to the same value.  If JOB = 'L', IFAILR is

              not referenced.

      INFO    (output) INTEGER
              = 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 larg-
      est magnitude has magnitude 1; here the magnitude of a com-
      plex number (x,y) is taken to be |x|+|y|.