Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

sppequ (3p)

Name

sppequ - metric positive definite matrix A in packed storage and reduce its con- dition number (with respect to the two-norm)

Synopsis

SUBROUTINE SPPEQU(UPLO, N, A, SCALE, SCOND, AMAX, INFO)

CHARACTER*1 UPLO
INTEGER N, INFO
REAL SCOND, AMAX
REAL A(*), SCALE(*)

SUBROUTINE SPPEQU_64(UPLO, N, A, SCALE, SCOND, AMAX, INFO)

CHARACTER*1 UPLO
INTEGER*8 N, INFO
REAL SCOND, AMAX
REAL A(*), SCALE(*)




F95 INTERFACE
SUBROUTINE PPEQU(UPLO, N, A, SCALE, SCOND, AMAX, INFO)

CHARACTER(LEN=1) :: UPLO
INTEGER :: N, INFO
REAL :: SCOND, AMAX
REAL, DIMENSION(:) :: A, SCALE

SUBROUTINE PPEQU_64(UPLO, N, A, SCALE, SCOND, AMAX, INFO)

CHARACTER(LEN=1) :: UPLO
INTEGER(8) :: N, INFO
REAL :: SCOND, AMAX
REAL, DIMENSION(:) :: A, SCALE




C INTERFACE
#include <sunperf.h>

void  sppequ(char  uplo,  int  n, float *a, float *scale, float *scond,
float *amax, int *info);

void sppequ_64(char uplo, long n, float *a, float *scale, float *scond,
float *amax, long *info);

Description

Oracle Solaris Studio Performance Library                           sppequ(3P)



NAME
       sppequ - compute row and column scalings intended to equilibrate a sym-
       metric positive definite matrix A in packed storage and reduce its con-
       dition number (with respect to the two-norm)


SYNOPSIS
       SUBROUTINE SPPEQU(UPLO, N, A, SCALE, SCOND, AMAX, INFO)

       CHARACTER*1 UPLO
       INTEGER N, INFO
       REAL SCOND, AMAX
       REAL A(*), SCALE(*)

       SUBROUTINE SPPEQU_64(UPLO, N, A, SCALE, SCOND, AMAX, INFO)

       CHARACTER*1 UPLO
       INTEGER*8 N, INFO
       REAL SCOND, AMAX
       REAL A(*), SCALE(*)




   F95 INTERFACE
       SUBROUTINE PPEQU(UPLO, N, A, SCALE, SCOND, AMAX, INFO)

       CHARACTER(LEN=1) :: UPLO
       INTEGER :: N, INFO
       REAL :: SCOND, AMAX
       REAL, DIMENSION(:) :: A, SCALE

       SUBROUTINE PPEQU_64(UPLO, N, A, SCALE, SCOND, AMAX, INFO)

       CHARACTER(LEN=1) :: UPLO
       INTEGER(8) :: N, INFO
       REAL :: SCOND, AMAX
       REAL, DIMENSION(:) :: A, SCALE




   C INTERFACE
       #include <sunperf.h>

       void  sppequ(char  uplo,  int  n, float *a, float *scale, float *scond,
                 float *amax, int *info);

       void sppequ_64(char uplo, long n, float *a, float *scale, float *scond,
                 float *amax, long *info);



PURPOSE
       sppequ  computes row and column scalings intended to equilibrate a sym-
       metric positive definite matrix A in packed storage and reduce its con-
       dition  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 condition number over all possible diagonal scalings.


ARGUMENTS
       UPLO (input)
                 = 'U':  Upper triangle of A is stored;
                 = 'L':  Lower triangle of A is stored.


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


       A (input) REAL array, dimension (N*(N+1)/2)
                 The upper or lower triangle of the symmetric matrix A, packed
                 columnwise in a linear array.  The j-th column of A is stored
                 in  the array A as follows: if UPLO = 'U', A(i + (j-1)*j/2) =
                 A(i,j) for 1<=i<=j; if UPLO = 'L', A(i  +  (j-1)*(2n-j)/2)  =
                 A(i,j) for j<=i<=n.


       SCALE (output) REAL array, dimension (N)
                 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                        sppequ(3P)