Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dgeequb (3p)

Name

dgeequb - by-N matrix A and reduce its condition number

Synopsis

SUBROUTINE DGEEQUB(M, N, A, LDA, R, C, ROWCND, COLCND, AMAX, INFO)


INTEGER INFO, LDA, M, N

DOUBLE PRECISION AMAX, COLCND, ROWCND

DOUBLE PRECISION A(LDA,*), C(*), R(*)


SUBROUTINE DGEEQUB_64(M, N, A, LDA, R, C, ROWCND, COLCND, AMAX, INFO)


INTEGER*8 INFO, LDA, M, N

DOUBLE PRECISION AMAX, COLCND, ROWCND

DOUBLE PRECISION A(LDA,*), C(*), R(*)


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


INTEGER :: M, N, LDA, INFO

REAL(8), DIMENSION(:,:) :: A

REAL(8), DIMENSION(:) :: R, C

REAL(8) :: ROWCND, COLCND, AMAX


SUBROUTINE GEEQUB_64(M, N, A, LDA, R, C, ROWCND, COLCND, AMAX, INFO)


INTEGER(8) :: M, N, LDA, INFO

REAL(8), DIMENSION(:,:) :: A

REAL(8), DIMENSION(:) :: R, C

REAL(8) :: ROWCND, COLCND, AMAX


C INTERFACE
#include <sunperf.h>

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


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

Description

Oracle Solaris Studio Performance Library                          dgeequb(3P)



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


SYNOPSIS
       SUBROUTINE DGEEQUB(M, N, A, LDA, R, C, ROWCND, COLCND, AMAX, INFO)


       INTEGER INFO, LDA, M, N

       DOUBLE PRECISION AMAX, COLCND, ROWCND

       DOUBLE PRECISION A(LDA,*), C(*), R(*)


       SUBROUTINE DGEEQUB_64(M, N, A, LDA, R, C, ROWCND, COLCND, AMAX, INFO)


       INTEGER*8 INFO, LDA, M, N

       DOUBLE PRECISION AMAX, COLCND, ROWCND

       DOUBLE PRECISION A(LDA,*), C(*), R(*)


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


       INTEGER :: M, N, LDA, INFO

       REAL(8), DIMENSION(:,:) :: A

       REAL(8), DIMENSION(:) :: R, C

       REAL(8) :: ROWCND, COLCND, AMAX


       SUBROUTINE GEEQUB_64(M, N, A, LDA, R, C, ROWCND, COLCND, AMAX, INFO)


       INTEGER(8) :: M, N, LDA, INFO

       REAL(8), DIMENSION(:,:) :: A

       REAL(8), DIMENSION(:) :: R, C

       REAL(8) :: ROWCND, COLCND, AMAX


   C INTERFACE
       #include <sunperf.h>

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


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


PURPOSE
       dgeequb  computes row and column scalings intended to equilibrate an M-
       by-N 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 an absolute value of at most the radix.

       R(i)  and C(j) are restricted to be a power of the radix between SMLNUM
       = smallest safe number 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.

       This routine differs from DGEEQU by restricting the scaling factors  to
       a  power  of  the  radix.  Baring over- and underflow, scaling by these
       factors introduces no additional rounding errors.  However, the  scaled
       entries'  magnitured  are  no  longer  approximately  1 but lie between
       sqrt(radix) and 1/sqrt(radix).


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


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


       A (input)
                 A is DOUBLE PRECISION array, dimension (LDA,N)
                 The M-by-N matrix whose equilibration factors are to be  com-
                 puted.


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


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


       C (output)
                 C is DOUBLE PRECISION array, dimension (N)
                 If INFO = 0,  C contains the column scale factors for A.


       ROWCND (output)
                 ROWCND is DOUBLE PRECISION
                 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)
                 COLCND is DOUBLE PRECISION
                 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)
                 AMAX is DOUBLE PRECISION
                 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)
                 INFO is INTEGER
                 = 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                       dgeequb(3P)