Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dsyequb (3p)

Name

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

Synopsis

SUBROUTINE DSYEQUB(UPLO, N, A, LDA, S, SCOND, AMAX, WORK, INFO)


INTEGER INFO, LDA, N

DOUBLE PRECISION AMAX, SCOND

CHARACTER*1 UPLO

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


SUBROUTINE DSYEQUB_64(UPLO, N, A, LDA, S, SCOND, AMAX, WORK, INFO)


INTEGER*8 INFO, LDA, N

DOUBLE PRECISION AMAX, SCOND

CHARACTER*1 UPLO

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


F95 INTERFACE
SUBROUTINE SYEQUB(UPLO, N, A, LDA, S, SCOND, AMAX, WORK, INFO)


INTEGER :: N, LDA, INFO

CHARACTER(LEN=1) :: UPLO

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

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

REAL(8) :: SCOND, AMAX


SUBROUTINE SYEQUB_64(UPLO, N, A, LDA, S, SCOND, AMAX, WORK, INFO)


INTEGER(8) :: N, LDA, INFO

CHARACTER(LEN=1) :: UPLO

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

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

REAL(8) :: SCOND, AMAX


C INTERFACE
#include <sunperf.h>

void  dsyequb  (char uplo, int n, double *a, int lda, double *s, double
*scond, double *amax, int *info);


void dsyequb_64 (char uplo, long n, double *a,  long  lda,  double  *s,
double *scond, double *amax, long *info);

Description

Oracle Solaris Studio Performance Library                          dsyequb(3P)



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


SYNOPSIS
       SUBROUTINE DSYEQUB(UPLO, N, A, LDA, S, SCOND, AMAX, WORK, INFO)


       INTEGER INFO, LDA, N

       DOUBLE PRECISION AMAX, SCOND

       CHARACTER*1 UPLO

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


       SUBROUTINE DSYEQUB_64(UPLO, N, A, LDA, S, SCOND, AMAX, WORK, INFO)


       INTEGER*8 INFO, LDA, N

       DOUBLE PRECISION AMAX, SCOND

       CHARACTER*1 UPLO

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


   F95 INTERFACE
       SUBROUTINE SYEQUB(UPLO, N, A, LDA, S, SCOND, AMAX, WORK, INFO)


       INTEGER :: N, LDA, INFO

       CHARACTER(LEN=1) :: UPLO

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

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

       REAL(8) :: SCOND, AMAX


       SUBROUTINE SYEQUB_64(UPLO, N, A, LDA, S, SCOND, AMAX, WORK, INFO)


       INTEGER(8) :: N, LDA, INFO

       CHARACTER(LEN=1) :: UPLO

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

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

       REAL(8) :: SCOND, AMAX


   C INTERFACE
       #include <sunperf.h>

       void  dsyequb  (char uplo, int n, double *a, int lda, double *s, double
                 *scond, double *amax, int *info);


       void dsyequb_64 (char uplo, long n, double *a,  long  lda,  double  *s,
                 double *scond, double *amax, long *info);


PURPOSE
       dsyequb computes row and column scalings intended to equilibrate a sym-
       metric 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 condition  number  over  all
       possible diagonal scalings.


ARGUMENTS
       UPLO (input)
                 UPLO is CHARACTER*1
                 Specifies whether the details of the factorization are stored
                 as an upper or lower triangular matrix.
                 = 'U':  Upper triangular, form is A = U*D*U**T;
                 = 'L':  Lower triangular, form is A = L*D*L**T.


       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 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.


       WORK (output)
                 WORK is DOUBLE PRECISION array, dimension (3*N)


       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                       dsyequb(3P)