Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cggbal (3p)

Name

cggbal - balance a pair of general complex matrices (A,B)

Synopsis

SUBROUTINE CGGBAL(JOB, N, A, LDA, B, LDB, ILO, IHI, LSCALE, RSCALE,
WORK, INFO)

CHARACTER*1 JOB
COMPLEX A(LDA,*), B(LDB,*)
INTEGER N, LDA, LDB, ILO, IHI, INFO
REAL LSCALE(*), RSCALE(*), WORK(*)

SUBROUTINE CGGBAL_64(JOB, N, A, LDA, B, LDB, ILO, IHI, LSCALE,
RSCALE, WORK, INFO)

CHARACTER*1 JOB
COMPLEX A(LDA,*), B(LDB,*)
INTEGER*8 N, LDA, LDB, ILO, IHI, INFO
REAL LSCALE(*), RSCALE(*), WORK(*)




F95 INTERFACE
SUBROUTINE GGBAL(JOB, N, A, LDA, B, LDB, ILO, IHI, LSCALE,
RSCALE, WORK, INFO)

CHARACTER(LEN=1) :: JOB
COMPLEX, DIMENSION(:,:) :: A, B
INTEGER :: N, LDA, LDB, ILO, IHI, INFO
REAL, DIMENSION(:) :: LSCALE, RSCALE, WORK

SUBROUTINE GGBAL_64(JOB, N, A, LDA, B, LDB, ILO, IHI, LSCALE,
RSCALE, WORK, INFO)

CHARACTER(LEN=1) :: JOB
COMPLEX, DIMENSION(:,:) :: A, B
INTEGER(8) :: N, LDA, LDB, ILO, IHI, INFO
REAL, DIMENSION(:) :: LSCALE, RSCALE, WORK




C INTERFACE
#include <sunperf.h>

void  cggbal(char job, int n, complex *a, int lda, complex *b, int ldb,
int *ilo, int *ihi, float *lscale, float *rscale, int *info);

void cggbal_64(char job, long n, complex *a, long lda, complex *b, long
ldb, long *ilo, long *ihi, float *lscale, float *rscale, long
*info);

Description

Oracle Solaris Studio Performance Library                           cggbal(3P)



NAME
       cggbal - balance a pair of general complex matrices (A,B)


SYNOPSIS
       SUBROUTINE CGGBAL(JOB, N, A, LDA, B, LDB, ILO, IHI, LSCALE, RSCALE,
             WORK, INFO)

       CHARACTER*1 JOB
       COMPLEX A(LDA,*), B(LDB,*)
       INTEGER N, LDA, LDB, ILO, IHI, INFO
       REAL LSCALE(*), RSCALE(*), WORK(*)

       SUBROUTINE CGGBAL_64(JOB, N, A, LDA, B, LDB, ILO, IHI, LSCALE,
             RSCALE, WORK, INFO)

       CHARACTER*1 JOB
       COMPLEX A(LDA,*), B(LDB,*)
       INTEGER*8 N, LDA, LDB, ILO, IHI, INFO
       REAL LSCALE(*), RSCALE(*), WORK(*)




   F95 INTERFACE
       SUBROUTINE GGBAL(JOB, N, A, LDA, B, LDB, ILO, IHI, LSCALE,
              RSCALE, WORK, INFO)

       CHARACTER(LEN=1) :: JOB
       COMPLEX, DIMENSION(:,:) :: A, B
       INTEGER :: N, LDA, LDB, ILO, IHI, INFO
       REAL, DIMENSION(:) :: LSCALE, RSCALE, WORK

       SUBROUTINE GGBAL_64(JOB, N, A, LDA, B, LDB, ILO, IHI, LSCALE,
              RSCALE, WORK, INFO)

       CHARACTER(LEN=1) :: JOB
       COMPLEX, DIMENSION(:,:) :: A, B
       INTEGER(8) :: N, LDA, LDB, ILO, IHI, INFO
       REAL, DIMENSION(:) :: LSCALE, RSCALE, WORK




   C INTERFACE
       #include <sunperf.h>

       void  cggbal(char job, int n, complex *a, int lda, complex *b, int ldb,
                 int *ilo, int *ihi, float *lscale, float *rscale, int *info);

       void cggbal_64(char job, long n, complex *a, long lda, complex *b, long
                 ldb, long *ilo, long *ihi, float *lscale, float *rscale, long
                 *info);



PURPOSE
       cggbal  balances  a  pair  of  general  complex  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 ele-
       ments on the diagonal;  and  second,  applying  a  diagonal  similarity
       transformation to rows and columns ILO to IHI to make the rows and col-
       umns as close in norm as possible. Both steps are optional.

       Balancing may reduce the 1-norm of the matrices, and improve the  accu-
       racy 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':  none:  simply set ILO = 1, IHI = N, LSCALE(I)  =  1.0
                 and RSCALE(I) = 1.0 for i=1,...,N; = 'P':  permute only;
                 = 'S':  scale only;
                 = 'B':  both permute and scale.


       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/output)
                 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)
                 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.


       LSCALE (output)
                 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  =  D(j)    for J = ILO,...,IHI = P(j)    for J =
                 IHI+1,...,N.  The order in which the interchanges are made is
                 N to IHI+1, then 1 to ILO-1.


       RSCALE (output)
                 Details  of  the  permutations and scaling factors applied to
                 the right side of A and B.  If P(j) is the index of the  col-
                 umn  interchanged with column j, and D(j) is the scaling fac-
                 tor applied to column j, then RSCALE(j) =  P(j)     for  J  =
                 1,...,ILO-1  =  D(j)    for J = ILO,...,IHI = P(j)    for J =
                 IHI+1,...,N.  The order in which the interchanges are made is
                 N to IHI+1, then 1 to ILO-1.


       WORK (workspace)
                 dimension(6*N)

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

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




                                  7 Nov 2015                        cggbal(3P)