Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

spoequ (3p)

Name

spoequ - metric positive definite matrix A and reduce its condition number (with respect to the two-norm)

Synopsis

SUBROUTINE SPOEQU(N, A, LDA, SCALE, SCOND, AMAX, INFO)

INTEGER N, LDA, INFO
REAL SCOND, AMAX
REAL A(LDA,*), SCALE(*)

SUBROUTINE SPOEQU_64(N, A, LDA, SCALE, SCOND, AMAX, INFO)

INTEGER*8 N, LDA, INFO
REAL SCOND, AMAX
REAL A(LDA,*), SCALE(*)




F95 INTERFACE
SUBROUTINE POEQU(N, A, LDA, SCALE, SCOND, AMAX, INFO)

INTEGER :: N, LDA, INFO
REAL :: SCOND, AMAX
REAL, DIMENSION(:) :: SCALE
REAL, DIMENSION(:,:) :: A

SUBROUTINE POEQU_64(N, A, LDA, SCALE, SCOND, AMAX, INFO)

INTEGER(8) :: N, LDA, INFO
REAL :: SCOND, AMAX
REAL, DIMENSION(:) :: SCALE
REAL, DIMENSION(:,:) :: A




C INTERFACE
#include <sunperf.h>

void spoequ(int n, float *a, int lda, float *scale, float *scond, float
*amax, int *info);

void spoequ_64(long n, float *a, long lda, float *scale, float  *scond,
float *amax, long *info);

Description

Oracle Solaris Studio Performance Library                           spoequ(3P)



NAME
       spoequ - compute 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)


SYNOPSIS
       SUBROUTINE SPOEQU(N, A, LDA, SCALE, SCOND, AMAX, INFO)

       INTEGER N, LDA, INFO
       REAL SCOND, AMAX
       REAL A(LDA,*), SCALE(*)

       SUBROUTINE SPOEQU_64(N, A, LDA, SCALE, SCOND, AMAX, INFO)

       INTEGER*8 N, LDA, INFO
       REAL SCOND, AMAX
       REAL A(LDA,*), SCALE(*)




   F95 INTERFACE
       SUBROUTINE POEQU(N, A, LDA, SCALE, SCOND, AMAX, INFO)

       INTEGER :: N, LDA, INFO
       REAL :: SCOND, AMAX
       REAL, DIMENSION(:) :: SCALE
       REAL, DIMENSION(:,:) :: A

       SUBROUTINE POEQU_64(N, A, LDA, SCALE, SCOND, AMAX, INFO)

       INTEGER(8) :: N, LDA, INFO
       REAL :: SCOND, AMAX
       REAL, DIMENSION(:) :: SCALE
       REAL, DIMENSION(:,:) :: A




   C INTERFACE
       #include <sunperf.h>

       void spoequ(int n, float *a, int lda, float *scale, float *scond, float
                 *amax, int *info);

       void spoequ_64(long n, float *a, long lda, float *scale, float  *scond,
                 float *amax, long *info);



PURPOSE
       spoequ  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) The order of the matrix A.  N >= 0.


       A (input) 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)
                 The leading dimension of the array A.  LDA >= max(1,N).


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


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


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




                                  7 Nov 2015                        spoequ(3P)