Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dgbequ (3p)

Name

dgbequ - by-N band matrix A and reduce its condition number

Synopsis

SUBROUTINE DGBEQU(M, N, KL, KU, A, LDA, R, C, ROWCND,
COLCND, AMAX, INFO)

INTEGER M, N, KL, KU, LDA, INFO
DOUBLE PRECISION ROWCND, COLCND, AMAX
DOUBLE PRECISION A(LDA,*), R(*), C(*)

SUBROUTINE DGBEQU_64(M, N, KL, KU, A, LDA, R, C, ROWCND,
COLCND, AMAX, INFO)

INTEGER*8 M, N, KL, KU, LDA, INFO
DOUBLE PRECISION ROWCND, COLCND, AMAX
DOUBLE PRECISION A(LDA,*), R(*), C(*)




F95 INTERFACE
SUBROUTINE GBEQU(M, N, KL, KU, A, LDA, R, C,
ROWCND, COLCND, AMAX, INFO)

INTEGER :: M, N, KL, KU, LDA, INFO
REAL(8) :: ROWCND, COLCND, AMAX
REAL(8), DIMENSION(:) :: R, C
REAL(8), DIMENSION(:,:) :: A

SUBROUTINE GBEQU_64(M, N, KL, KU, A, LDA, R, C,
ROWCND, COLCND, AMAX, INFO)

INTEGER(8) :: M, N, KL, KU, LDA, INFO
REAL(8) :: ROWCND, COLCND, AMAX
REAL(8), DIMENSION(:) :: R, C
REAL(8), DIMENSION(:,:) :: A




C INTERFACE
#include <sunperf.h>

void dgbequ(int m, int n, int kl, int ku, double *a,  int  lda,  double
*r,  double *c, double *rowcnd, double *colcnd, double *amax,
int *info);

void dgbequ_64(long m, long n, long kl, long ku, double *a,  long  lda,
double  *r, double *c, double *rowcnd, double *colcnd, double
*amax, long *info);

Description

Oracle Solaris Studio Performance Library                           dgbequ(3P)



NAME
       dgbequ  - compute row and column scalings intended to equilibrate an M-
       by-N band matrix A and reduce its condition number


SYNOPSIS
       SUBROUTINE DGBEQU(M, N, KL, KU, A, LDA, R, C, ROWCND,
             COLCND, AMAX, INFO)

       INTEGER M, N, KL, KU, LDA, INFO
       DOUBLE PRECISION ROWCND, COLCND, AMAX
       DOUBLE PRECISION A(LDA,*), R(*), C(*)

       SUBROUTINE DGBEQU_64(M, N, KL, KU, A, LDA, R, C, ROWCND,
             COLCND, AMAX, INFO)

       INTEGER*8 M, N, KL, KU, LDA, INFO
       DOUBLE PRECISION ROWCND, COLCND, AMAX
       DOUBLE PRECISION A(LDA,*), R(*), C(*)




   F95 INTERFACE
       SUBROUTINE GBEQU(M, N, KL, KU, A, LDA, R, C,
              ROWCND, COLCND, AMAX, INFO)

       INTEGER :: M, N, KL, KU, LDA, INFO
       REAL(8) :: ROWCND, COLCND, AMAX
       REAL(8), DIMENSION(:) :: R, C
       REAL(8), DIMENSION(:,:) :: A

       SUBROUTINE GBEQU_64(M, N, KL, KU, A, LDA, R, C,
              ROWCND, COLCND, AMAX, INFO)

       INTEGER(8) :: M, N, KL, KU, LDA, INFO
       REAL(8) :: ROWCND, COLCND, AMAX
       REAL(8), DIMENSION(:) :: R, C
       REAL(8), DIMENSION(:,:) :: A




   C INTERFACE
       #include <sunperf.h>

       void dgbequ(int m, int n, int kl, int ku, double *a,  int  lda,  double
                 *r,  double *c, double *rowcnd, double *colcnd, double *amax,
                 int *info);

       void dgbequ_64(long m, long n, long kl, long ku, double *a,  long  lda,
                 double  *r, double *c, double *rowcnd, double *colcnd, double
                 *amax, long *info);



PURPOSE
       dgbequ computes row and column scalings intended to equilibrate  an  M-
       by-N  band matrix A and reduce its condition number.  R returns the row
       scale factors and C the column scale factors, chosen to try to make the
       largest  element  in  each row and column of the matrix B with elements
       B(i,j)=R(i)*A(i,j)*C(j) have absolute value 1.

       R(i) and C(j) are restricted to be between SMLNUM = smallest safe  num-
       ber  and BIGNUM = largest safe number.  Use of these scaling factors is
       not guaranteed to reduce the condition number of A but  works  well  in
       practice.


ARGUMENTS
       M (input) The number of rows of the matrix A.  M >= 0.


       N (input) The number of columns of the matrix A.  N >= 0.


       KL (input)
                 The number of subdiagonals within the band of A.  KL >= 0.


       KU (input)
                 The  number of superdiagonals within the band of A.  KU >= 0.


       A (input) The band matrix A, stored in rows 1  to  KL+KU+1.   The  j-th
                 column  of  A  is stored in the j-th column of the array A as
                 follows:    A(ku+1+i-j,j)    =    A(i,j)     for     max(1,j-
                 ku)<=i<=min(m,j+kl).


       LDA (input)
                 The leading dimension of the array A.  LDA >= KL+KU+1.


       R (output)
                 If  INFO  =  0, or INFO > M, R contains the row scale factors
                 for A.


       C (output)
                 If INFO = 0, C contains the column scale factors for A.


       ROWCND (output)
                 If INFO = 0 or INFO > M, ROWCND contains  the  ratio  of  the
                 smallest R(i) to the largest R(i).  If ROWCND >= 0.1 and AMAX
                 is neither too large nor too small, it is not  worth  scaling
                 by R.


       COLCND (output)
                 If  INFO  = 0, COLCND contains the ratio of the smallest C(i)
                 to the largest C(i).  If COLCND >= 0.1, it is not worth scal-
                 ing by C.


       AMAX (output)
                 Absolute  value  of  largest matrix element.  If AMAX is very
                 close to overflow or very  close  to  underflow,  the  matrix
                 should be scaled.


       INFO (output)
                 = 0:  successful exit;
                 < 0:  if INFO = -i, the i-th argument had an illegal value;
                 > 0:  if INFO = i, and i is
                 <= M:  the i-th row of A is exactly zero;
                 >  M:  the (i-M)-th column of A is exactly zero.




                                  7 Nov 2015                        dgbequ(3P)