zpoequb - 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
SUBROUTINE ZPOEQUB(N, A, LDA, S, SCOND, AMAX, INFO) INTEGER INFO, LDA, N DOUBLE PRECISION AMAX, SCOND DOUBLE COMPLEX A(LDA,*) DOUBLE PRECISION S(*) SUBROUTINE ZPOEQUB_64(N, A, LDA, S, SCOND, AMAX, INFO) INTEGER*8 INFO, LDA, N DOUBLE PRECISION AMAX, SCOND DOUBLE COMPLEX A(LDA,*) DOUBLE PRECISION S(*) F95 INTERFACE SUBROUTINE POEQUB(N, A, LDA, S, SCOND, AMAX, INFO) INTEGER :: N, LDA, INFO REAL(8), DIMENSION(:) :: S COMPLEX(8), DIMENSION(:,:) :: A REAL(8) :: SCOND, AMAX SUBROUTINE POEQUB_64(N, A, LDA, S, SCOND, AMAX, INFO) INTEGER(8) :: N, LDA, INFO REAL(8), DIMENSION(:) :: S COMPLEX(8), DIMENSION(:,:) :: A REAL(8) :: SCOND, AMAX C INTERFACE #include <sunperf.h> void zpoequb (int n, doublecomplex *a, int lda, double *s, double *scond, double *amax, int *info); void zpoequb_64 (long n, doublecomplex *a, long lda, double *s, double *scond, double *amax, long *info);
Oracle Solaris Studio Performance Library zpoequb(3P)
NAME
zpoequb - 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 ZPOEQUB(N, A, LDA, S, SCOND, AMAX, INFO)
INTEGER INFO, LDA, N
DOUBLE PRECISION AMAX, SCOND
DOUBLE COMPLEX A(LDA,*)
DOUBLE PRECISION S(*)
SUBROUTINE ZPOEQUB_64(N, A, LDA, S, SCOND, AMAX, INFO)
INTEGER*8 INFO, LDA, N
DOUBLE PRECISION AMAX, SCOND
DOUBLE COMPLEX A(LDA,*)
DOUBLE PRECISION S(*)
F95 INTERFACE
SUBROUTINE POEQUB(N, A, LDA, S, SCOND, AMAX, INFO)
INTEGER :: N, LDA, INFO
REAL(8), DIMENSION(:) :: S
COMPLEX(8), DIMENSION(:,:) :: A
REAL(8) :: SCOND, AMAX
SUBROUTINE POEQUB_64(N, A, LDA, S, SCOND, AMAX, INFO)
INTEGER(8) :: N, LDA, INFO
REAL(8), DIMENSION(:) :: S
COMPLEX(8), DIMENSION(:,:) :: A
REAL(8) :: SCOND, AMAX
C INTERFACE
#include <sunperf.h>
void zpoequb (int n, doublecomplex *a, int lda, double *s, double
*scond, double *amax, int *info);
void zpoequb_64 (long n, doublecomplex *a, long lda, double *s, double
*scond, double *amax, long *info);
PURPOSE
zpoequb 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 COMPLEX*16 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 zpoequb(3P)