Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dgebal (3p)

Name

dgebal - balance a general real matrix A

Synopsis

SUBROUTINE DGEBAL(JOB, N, A, LDA, ILO, IHI, SCALE, INFO)

CHARACTER*1 JOB
INTEGER N, LDA, ILO, IHI, INFO
DOUBLE PRECISION A(LDA,*), SCALE(*)

SUBROUTINE DGEBAL_64(JOB, N, A, LDA, ILO, IHI, SCALE, INFO)

CHARACTER*1 JOB
INTEGER*8 N, LDA, ILO, IHI, INFO
DOUBLE PRECISION A(LDA,*), SCALE(*)




F95 INTERFACE
SUBROUTINE GEBAL(JOB, N, A, LDA, ILO, IHI, SCALE, INFO)

CHARACTER(LEN=1) :: JOB
INTEGER :: N, LDA, ILO, IHI, INFO
REAL(8), DIMENSION(:) :: SCALE
REAL(8), DIMENSION(:,:) :: A

SUBROUTINE GEBAL_64(JOB, N, A, LDA, ILO, IHI, SCALE, INFO)

CHARACTER(LEN=1) :: JOB
INTEGER(8) :: N, LDA, ILO, IHI, INFO
REAL(8), DIMENSION(:) :: SCALE
REAL(8), DIMENSION(:,:) :: A




C INTERFACE
#include <sunperf.h>

void  dgebal(char  job,  int n, double *a, int lda, int *ilo, int *ihi,
double *scale, int *info);

void dgebal_64(char job, long n, double *a, long lda, long  *ilo,  long
*ihi, double *scale, long *info);

Description

Oracle Solaris Studio Performance Library                           dgebal(3P)



NAME
       dgebal - balance a general real matrix A


SYNOPSIS
       SUBROUTINE DGEBAL(JOB, N, A, LDA, ILO, IHI, SCALE, INFO)

       CHARACTER*1 JOB
       INTEGER N, LDA, ILO, IHI, INFO
       DOUBLE PRECISION A(LDA,*), SCALE(*)

       SUBROUTINE DGEBAL_64(JOB, N, A, LDA, ILO, IHI, SCALE, INFO)

       CHARACTER*1 JOB
       INTEGER*8 N, LDA, ILO, IHI, INFO
       DOUBLE PRECISION A(LDA,*), SCALE(*)




   F95 INTERFACE
       SUBROUTINE GEBAL(JOB, N, A, LDA, ILO, IHI, SCALE, INFO)

       CHARACTER(LEN=1) :: JOB
       INTEGER :: N, LDA, ILO, IHI, INFO
       REAL(8), DIMENSION(:) :: SCALE
       REAL(8), DIMENSION(:,:) :: A

       SUBROUTINE GEBAL_64(JOB, N, A, LDA, ILO, IHI, SCALE, INFO)

       CHARACTER(LEN=1) :: JOB
       INTEGER(8) :: N, LDA, ILO, IHI, INFO
       REAL(8), DIMENSION(:) :: SCALE
       REAL(8), DIMENSION(:,:) :: A




   C INTERFACE
       #include <sunperf.h>

       void  dgebal(char  job,  int n, double *a, int lda, int *ilo, int *ihi,
                 double *scale, int *info);

       void dgebal_64(char job, long n, double *a, long lda, long  *ilo,  long
                 *ihi, double *scale, long *info);



PURPOSE
       dgebal balances a general real matrix A.  This involves, first, permut-
       ing A by a similarity transformation  to  isolate  eigenvalues  in  the
       first 1 to ILO-1 and last IHI+1 to N elements on the diagonal; and sec-
       ond, 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 matrix, and improve the accuracy
       of the computed eigenvalues and/or eigenvectors.  However, the diagonal
       transformation step can occasionally make the  norm  larger  and  hence
       degrade performance.


ARGUMENTS
       JOB (input)
                 Specifies the operations to be performed on A:
                 =  'N':   none:   simply set ILO = 1, IHI = N, SCALE(I) = 1.0
                 for i = 1,...,N; = 'P':  permute only;
                 = 'S':  scale only;
                 = 'B':  both permute and scale.


       N (input) The order of the matrix A.  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.  See
                 Further Details.


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


       ILO (output)
                 ILO and IHI are set to integers such that on exit A(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.


       SCALE (output)
                 Details of the permutations and scaling factors applied to A.
                 If  P(j) is the index of the row and column interchanged with
                 row and column j and D(j) is the scaling  factor  applied  to
                 row and column j, then SCALE(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.


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

FURTHER DETAILS
       The permutations consist of row and column interchanges which  put  the
       matrix in the form

                  ( T1   X   Y  )
          P A P = (  0   B   Z  )
                  (  0   0   T2 )

       where  T1  and  T2  are upper triangular matrices whose eigenvalues lie
       along the diagonal.  The column indices ILO and IHI mark  the  starting
       and ending columns of the submatrix B. Balancing consists of applying a
       diagonal similarity transformation inv(D) * B * D to make  the  1-norms
       of each row of B and its corresponding column nearly equal.  The output
       matrix is

          ( T1     X*D          Y    )
          (  0  inv(D)*B*D  inv(D)*Z ).
          (  0      0           T2   )

       Information about the permutations P  and  the  diagonal  matrix  D  is
       returned in the vector SCALE.

       This subroutine is based on the EISPACK routine BALANC.

       Modified by Tzu-Yi Chen, Computer Science Division, University of
         California at Berkeley, USA




                                  7 Nov 2015                        dgebal(3P)