rg Subroutine

private subroutine rg(Nm, n, a, Wr, Wi, Matz, z, Iv1, Fv1, Ierr)

Compute the eigenvalues and, optionally, the eigenvectors of a real general matrix.

This subroutine calls the recommended sequence of subroutines from the eigensystem subroutine package (EISPACK) To find the eigenvalues and eigenvectors (if desired) of a REAL GENERAL matrix.

References

  • B. T. Smith, J. M. Boyle, J. J. Dongarra, B. S. Garbow, Y. Ikebe, V. C. Klema and C. B. Moler, Matrix Eigen- system Routines - EISPACK Guide, Springer-Verlag, 1976.

Author

  • Smith, B. T., et al.

History (YYMMDD)

  • 760101 DATE WRITTEN
  • 890831 Modified array declarations. (WRB)
  • 890831 REVISION DATE from Version 3.2
  • 891214 Prologue converted to Version 4.0 format. (BAB)
  • 920501 Reformatted the REFERENCES section. (WRB)
  • 921103 Corrected description of IV1. (DWL, FNF and WRB)
  • Jacob Williams, refactored into modern Fortran (3/25/2018)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: Nm

must be set to the row dimension of the two-dimensional array parameters, A and Z, as declared in the calling program dimension statement.

integer, intent(in) :: n

the order of the matrix A. N must be less than or equal to NM.

real(kind=wp), intent(inout) :: a(Nm,*)

contains the real general matrix. dimensioned A(NM,N). Note: A is destroyed on output.

real(kind=wp), intent(out) :: Wr(*)

real part of the eigenvalues. The eigenvalues are unordered except that complex conjugate pairs of eigenvalues appear consecutively with the eigenvalue having the positive imaginary part first. If an error exit is made, the eigenvalues should be correct for indices IERR+1, IERR+2, ..., N. WR and WI are one-dimensional REAL arrays, dimensioned WR(N) and WI(N).

real(kind=wp), intent(out) :: Wi(*)

imaginary part of the eigenvalues.

integer, intent(in) :: Matz

an INTEGER variable set equal to zero if only eigenvalues are desired. Otherwise, it is set to any non-zero integer for both eigenvalues and eigenvectors.

real(kind=wp), intent(out) :: z(Nm,*)

contains the real and imaginary parts of the eigenvectors if MATZ is not zero. If the J-th eigenvalue is real, the J-th column of Z contains its eigenvector. If the J-th eigenvalue is complex with positive imaginary part, the J-th and (J+1)-th columns of Z contain the real and imaginary parts of its eigenvector. The conjugate of this vector is the eigenvector for the conjugate eigenvalue. Z is a two-dimensional REAL array, dimensioned Z(NM,N).

integer, intent(inout) :: Iv1(*)

one-dimensional temporary storage arrays of dimension N.

real(kind=wp), intent(inout) :: Fv1(*)

one-dimensional temporary storage arrays of dimension N.

integer, intent(out) :: Ierr

an INTEGER flag set to:

  • 0 -- for normal return,
  • 10*N -- if N is greater than NM,
  • J -- if the J-th eigenvalue has not been determined after a total of 30 iterations. The eigenvalues should be correct for indices IERR+1, IERR+2, ..., N, but no eigenvectors are computed.

Calls

proc~~rg~~CallsGraph proc~rg eispack_module::rg proc~balanc eispack_module::balanc proc~rg->proc~balanc proc~balbak eispack_module::balbak proc~rg->proc~balbak proc~elmhes eispack_module::elmhes proc~rg->proc~elmhes proc~eltran eispack_module::eltran proc~rg->proc~eltran proc~hqr eispack_module::hqr proc~rg->proc~hqr proc~hqr2 eispack_module::hqr2 proc~rg->proc~hqr2 proc~cdiv eispack_module::cdiv proc~hqr2->proc~cdiv

Called by

proc~~rg~~CalledByGraph proc~rg eispack_module::rg proc~compute_eigenvalues_and_eigenvectors eispack_module::compute_eigenvalues_and_eigenvectors proc~compute_eigenvalues_and_eigenvectors->proc~rg proc~compute_real_eigenvalues_and_normalized_eigenvectors eispack_module::compute_real_eigenvalues_and_normalized_eigenvectors proc~compute_real_eigenvalues_and_normalized_eigenvectors->proc~compute_eigenvalues_and_eigenvectors proc~eispack_test eispack_module::eispack_test proc~eispack_test->proc~compute_eigenvalues_and_eigenvectors

Source Code

 subroutine rg(Nm, n, a, Wr, Wi, Matz, z, Iv1, Fv1, Ierr)

    implicit none

    integer,intent(in)  :: n   !! the order of the matrix A.
                               !! N must be less than or equal to NM.
    integer,intent(in)  :: Nm  !! must be set to the row dimension of the two-dimensional
                               !! array parameters, A and Z, as declared in the calling
                               !! program dimension statement.
    integer,intent(in)  :: Matz !! an INTEGER variable set equal to zero if only
                                !! eigenvalues are desired.  Otherwise, it is set to any
                                !! non-zero integer for both eigenvalues and eigenvectors.
    real(wp),intent(inout) :: a(Nm, *)   !! contains the real general matrix.
                                         !! dimensioned A(NM,N).
                                         !! Note: A is destroyed on output.
    integer,intent(out)  :: Ierr  !! an INTEGER flag set to:
                                  !!
                                  !! * 0 -- for normal return,
                                  !! * 10*N -- if N is greater than NM,
                                  !! * J    -- if the J-th eigenvalue has not been
                                  !!           determined after a total of 30 iterations.
                                  !!           The eigenvalues should be correct for indices
                                  !!           IERR+1, IERR+2, ..., N, but no eigenvectors are
                                  !!           computed.
    real(wp),intent(out) :: Wr(*)  !! real part of the eigenvalues.  The eigenvalues are unordered except
                                   !! that complex conjugate pairs of eigenvalues appear consecutively
                                   !! with the eigenvalue having the positive imaginary part
                                   !! first.  If an error exit is made, the eigenvalues should be
                                   !! correct for indices IERR+1, IERR+2, ..., N.  WR and WI are
                                   !! one-dimensional REAL arrays, dimensioned WR(N) and WI(N).
    real(wp),intent(out) :: Wi(*)  !! imaginary part of the eigenvalues.
    real(wp),intent(out) :: z(Nm, *) !! contains the real and imaginary parts of the eigenvectors
                                     !! if MATZ is not zero.  If the J-th eigenvalue is real, the
                                     !! J-th column of Z contains its eigenvector.  If the J-th
                                     !! eigenvalue is complex with positive imaginary part, the
                                     !! J-th and (J+1)-th columns of Z contain the real and
                                     !! imaginary parts of its eigenvector.  The conjugate of this
                                     !! vector is the eigenvector for the conjugate eigenvalue.
                                     !! Z is a two-dimensional REAL array, dimensioned Z(NM,N).
    real(wp),intent(inout) :: Fv1(*) !! one-dimensional temporary storage arrays of dimension N.
    integer,intent(inout)  :: Iv1(*) !! one-dimensional temporary storage arrays of dimension N.

    integer  :: is1
    integer  :: is2

    if (n <= Nm) then
       call balanc(Nm, n, a, is1, is2, Fv1)
       call elmhes(Nm, n, is1, is2, a, Iv1)
       if (Matz /= 0) then
          ! find both eigenvalues and eigenvectors
          call eltran(Nm, n, is1, is2, a, Iv1, z)
          call hqr2(Nm, n, is1, is2, a, Wr, Wi, z, Ierr)
          if (Ierr == 0) call balbak(Nm, n, is1, is2, Fv1, n, z)
       else
          ! find eigenvalues only
          call hqr(Nm, n, is1, is2, a, Wr, Wi, Ierr)
       endif
    else
       Ierr = 10*n
    endif

 end subroutine rg