dggbal


NAME

dggbal - balance a pair of general real matrices (A,B)


SYNOPSIS

  SUBROUTINE DGGBAL( JOB, N, A, LDA, B, LDB, ILO, IHI, LSCALE, RSCALE, 
 *      WORK, INFO)
  CHARACTER * 1 JOB
  INTEGER N, LDA, LDB, ILO, IHI, INFO
  DOUBLE PRECISION A(LDA,*), B(LDB,*), LSCALE(*), RSCALE(*), WORK(*)
 
  SUBROUTINE DGGBAL_64( JOB, N, A, LDA, B, LDB, ILO, IHI, LSCALE, 
 *      RSCALE, WORK, INFO)
  CHARACTER * 1 JOB
  INTEGER*8 N, LDA, LDB, ILO, IHI, INFO
  DOUBLE PRECISION A(LDA,*), B(LDB,*), LSCALE(*), RSCALE(*), WORK(*)
 

F95 INTERFACE

  SUBROUTINE GGBAL( JOB, [N], A, [LDA], B, [LDB], ILO, IHI, LSCALE, 
 *       RSCALE, [WORK], [INFO])
  CHARACTER(LEN=1) :: JOB
  INTEGER :: N, LDA, LDB, ILO, IHI, INFO
  REAL(8), DIMENSION(:) :: LSCALE, RSCALE, WORK
  REAL(8), DIMENSION(:,:) :: A, B
 
  SUBROUTINE GGBAL_64( JOB, [N], A, [LDA], B, [LDB], ILO, IHI, LSCALE, 
 *       RSCALE, [WORK], [INFO])
  CHARACTER(LEN=1) :: JOB
  INTEGER(8) :: N, LDA, LDB, ILO, IHI, INFO
  REAL(8), DIMENSION(:) :: LSCALE, RSCALE, WORK
  REAL(8), DIMENSION(:,:) :: A, B
 

C INTERFACE

#include <sunperf.h>

void dggbal(char job, int n, double *a, int lda, double *b, int ldb, int *ilo, int *ihi, double *lscale, double *rscale, int *info);

void dggbal_64(char job, long n, double *a, long lda, double *b, long ldb, long *ilo, long *ihi, double *lscale, double *rscale, long *info);


PURPOSE

dggbal balances a pair of general real matrices (A,B). This involves, first, permuting A and B by similarity transformations to isolate eigenvalues in the first 1 to ILO$-$1 and last IHI+1 to N elements on the diagonal; and second, applying a diagonal similarity transformation to rows and columns ILO to IHI to make the rows and columns as close in norm as possible. Both steps are optional.

Balancing may reduce the 1-norm of the matrices, and improve the accuracy of the computed eigenvalues and/or eigenvectors in the generalized eigenvalue problem A*x = lambda*B*x.


ARGUMENTS

* JOB (input)
Specifies the operations to be performed on A and B:

* N (input)
The order of the matrices A and B. N >= 0.

* A (input/output)
On entry, the input matrix A. On exit, A is overwritten by the balanced matrix. If JOB = 'N', A is not referenced.

* LDA (input)
The leading dimension of the array A. LDA >= max(1,N).

* B (input)
On entry, the input matrix B. On exit, B is overwritten by the balanced matrix. If JOB = 'N', B is not referenced.

* LDB (input)
The leading dimension of the array B. LDB >= max(1,N).

* ILO (output)
ILO and IHI are set to integers such that on exit A(i,j) = 0 and B(i,j) = 0 if i > j and j = 1,...,ILO-1 or i = IHI+1,...,N. If JOB = 'N' or 'S', ILO = 1 and IHI = N.

* IHI (output)
See the description for ILO.

* LSCALE (input)
Details of the permutations and scaling factors applied to the left side of A and B. If P(j) is the index of the row interchanged with row j, and D(j) is the scaling factor applied to row j, then LSCALE(j) = P(j) for J = 1,...,ILO-1

* RSCALE (input)
Details of the permutations and scaling factors applied to the right side of A and B. If P(j) is the index of the column interchanged with column j, and D(j) is the scaling factor applied to column j, then LSCALE(j) = P(j) for J = 1,...,ILO-1

* WORK (workspace)
dimension(6*N)

* INFO (output)