Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dpoequb (3p)

Name

dpoequb - compute row and column scalings intended to equilibrate a symmetric positive definite matrix A and reduce its condition number with respect to the two-norm

Synopsis

SUBROUTINE DPOEQUB(N, A, LDA, S, SCOND, AMAX, INFO)


INTEGER INFO, LDA, N

DOUBLE PRECISION AMAX, SCOND

DOUBLE PRECISION A(LDA,*), S(*)


SUBROUTINE DPOEQUB_64(N, A, LDA, S, SCOND, AMAX, INFO)


INTEGER*8 INFO, LDA, N

DOUBLE PRECISION AMAX, SCOND

DOUBLE PRECISION A(LDA,*), S(*)


F95 INTERFACE
SUBROUTINE POEQUB(N, A, LDA, S, SCOND, AMAX, INFO)


INTEGER :: N, LDA, INFO

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

REAL(8), DIMENSION(:) :: S

REAL(8) :: SCOND, AMAX


SUBROUTINE POEQUB_64(N, A, LDA, S, SCOND, AMAX, INFO)


INTEGER(8) :: N, LDA, INFO

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

REAL(8), DIMENSION(:) :: S

REAL(8) :: SCOND, AMAX


C INTERFACE
#include <sunperf.h>

void dpoequb (int n, double *a, int lda, double *s, double *scond, dou-
ble *amax, int *info);


void dpoequb_64 (long n, double *a, long lda, double *s, double *scond,
double *amax, long *info);

Description

Oracle Solaris Studio Performance Library                          dpoequb(3P)



NAME
       dpoequb  -  compute  row  and column scalings intended to equilibrate a
       symmetric positive definite matrix A and reduce  its  condition  number
       with respect to the two-norm


SYNOPSIS
       SUBROUTINE DPOEQUB(N, A, LDA, S, SCOND, AMAX, INFO)


       INTEGER INFO, LDA, N

       DOUBLE PRECISION AMAX, SCOND

       DOUBLE PRECISION A(LDA,*), S(*)


       SUBROUTINE DPOEQUB_64(N, A, LDA, S, SCOND, AMAX, INFO)


       INTEGER*8 INFO, LDA, N

       DOUBLE PRECISION AMAX, SCOND

       DOUBLE PRECISION A(LDA,*), S(*)


   F95 INTERFACE
       SUBROUTINE POEQUB(N, A, LDA, S, SCOND, AMAX, INFO)


       INTEGER :: N, LDA, INFO

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

       REAL(8), DIMENSION(:) :: S

       REAL(8) :: SCOND, AMAX


       SUBROUTINE POEQUB_64(N, A, LDA, S, SCOND, AMAX, INFO)


       INTEGER(8) :: N, LDA, INFO

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

       REAL(8), DIMENSION(:) :: S

       REAL(8) :: SCOND, AMAX


   C INTERFACE
       #include <sunperf.h>

       void dpoequb (int n, double *a, int lda, double *s, double *scond, dou-
                 ble *amax, int *info);


       void dpoequb_64 (long n, double *a, long lda, double *s, double *scond,
                 double *amax, long *info);


PURPOSE
       dpoequb computes row and column scalings intended to equilibrate a sym-
       metric positive definite matrix A and reduce its condition number (with
       respect  to  the  two-norm).   S  contains  the  scale  factors, S(i) =
       1/sqrt(A(i,i)), chosen so that the scaled matrix B with elements B(i,j)
       = S(i)*A(i,j)*S(j) has ones on the diagonal.  This choice of S puts the
       condition number of B within a factor N of the smallest possible condi-
       tion number over all possible diagonal scalings.


ARGUMENTS
       N (input)
                 N is INTEGER
                 The order of the matrix A.  N >= 0.


       A (input)
                 A is DOUBLE PRECISION array, dimension (LDA,N)
                 The  N-by-N  symmetric positive definite matrix whose scaling
                 factors are to be computed.  Only the diagonal elements of  A
                 are referenced.


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


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


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


       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, the i-th diagonal element is nonpositive.



                                  7 Nov 2015                       dpoequb(3P)