Contents


NAME

     dggbak - form the right or left eigenvectors of a real  gen-
     eralized  eigenvalue  problem  A*x = lambda*B*x, by backward
     transformation on the computed eigenvectors of the  balanced
     pair of matrices output by DGGBAL

SYNOPSIS

     SUBROUTINE DGGBAK(JOB, SIDE, N, ILO, IHI, LSCALE, RSCALE, M, V, LDV,
           INFO)

     CHARACTER * 1 JOB, SIDE
     INTEGER N, ILO, IHI, M, LDV, INFO
     DOUBLE PRECISION LSCALE(*), RSCALE(*), V(LDV,*)

     SUBROUTINE DGGBAK_64(JOB, SIDE, N, ILO, IHI, LSCALE, RSCALE, M, V,
           LDV, INFO)

     CHARACTER * 1 JOB, SIDE
     INTEGER*8 N, ILO, IHI, M, LDV, INFO
     DOUBLE PRECISION LSCALE(*), RSCALE(*), V(LDV,*)

  F95 INTERFACE
     SUBROUTINE GGBAK(JOB, SIDE, [N], ILO, IHI, LSCALE, RSCALE, [M], V,
            [LDV], [INFO])

     CHARACTER(LEN=1) :: JOB, SIDE
     INTEGER :: N, ILO, IHI, M, LDV, INFO
     REAL(8), DIMENSION(:) :: LSCALE, RSCALE
     REAL(8), DIMENSION(:,:) :: V

     SUBROUTINE GGBAK_64(JOB, SIDE, [N], ILO, IHI, LSCALE, RSCALE, [M], V,
            [LDV], [INFO])

     CHARACTER(LEN=1) :: JOB, SIDE
     INTEGER(8) :: N, ILO, IHI, M, LDV, INFO
     REAL(8), DIMENSION(:) :: LSCALE, RSCALE
     REAL(8), DIMENSION(:,:) :: V

  C INTERFACE
     #include <sunperf.h>

     void dggbak(char job, char side, int n, int  ilo,  int  ihi,
               double  *lscale, double *rscale, int m, double *v,
               int ldv, int *info);

     void dggbak_64(char job, char side, long n, long  ilo,  long
               ihi,  double  *lscale,  double  *rscale,  long  m,
               double *v, long ldv, long *info);

PURPOSE

     dggbak forms the right or left eigenvectors of a  real  gen-
     eralized  eigenvalue  problem  A*x = lambda*B*x, by backward
     transformation on the computed eigenvectors of the  balanced
     pair of matrices output by DGGBAL.

ARGUMENTS

     JOB (input)
               Specifies  the  type  of  backward  transformation
               required:
               = 'N':  do nothing, return immediately;
               = 'P':  do backward transformation for permutation
               only;
               = 'S':  do  backward  transformation  for  scaling
               only;
               = 'B':  do backward transformations for both  per-
               mutation and scaling.  JOB must be the same as the
               argument JOB supplied to DGGBAL.

     SIDE (input)
               = 'R':  V contains right eigenvectors;
               = 'L':  V contains left eigenvectors.

     N (input) The number of rows of the matrix V.  N >= 0.

     ILO (input)
               The integers ILO and IHI determined by DGGBAL.   1
               <=  ILO <= IHI <= N, if N > 0; ILO=1 and IHI=0, if
               N=0.

     IHI (input)
               See the description for ILO.

     LSCALE (input)
               Details of the permutations and/or scaling factors
               applied  to  the left side of A and B, as returned
               by DGGBAL.

     RSCALE (input)
               Details of the permutations and/or scaling factors
               applied  to the right side of A and B, as returned
               by DGGBAL.

     M (input) The number of columns of the matrix V.  M >= 0.

     V (input/output)
               On entry, the matrix of right or left eigenvectors
               to  be  transformed,  as  returned  by STGEVC.  On
               exit, V is overwritten by the  transformed  eigen-
               vectors.

     LDV (input)
               The leading dimension of  the  matrix  V.  LDV  >=
               max(1,N).

     INFO (output)
               = 0:  successful exit.
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value.

FURTHER DETAILS

     See R.C. Ward, Balancing the generalized eigenvalue problem,
                    SIAM J. Sci. Stat. Comp. 2 (1981), 141-152.