dla_lin_berr - wise relative backward error
SUBROUTINE DLA_LIN_BERR (N, NZ, NRHS, RES, AYB, BERR) INTEGER N, NZ, NRHS DOUBLE PRECISION AYB(N,NRHS), BERR(NRHS) DOUBLE PRECISION RES(N,NRHS) SUBROUTINE DLA_LIN_BERR_64 (N, NZ, NRHS, RES, AYB, BERR) INTEGER*8 N, NZ, NRHS DOUBLE PRECISION AYB(N,NRHS), BERR(NRHS) DOUBLE PRECISION RES(N,NRHS) F95 INTERFACE SUBROUTINE LA_LIN_BERR (N, NZ, NRHS, RES, AYB, BERR) INTEGER :: N, NZ, NRHS REAL(8), DIMENSION(:,:) :: RES, AYB REAL(8), DIMENSION(:) :: BERR SUBROUTINE LA_LIN_BERR_64 (N, NZ, NRHS, RES, AYB, BERR) INTEGER(8) :: N, NZ, NRHS REAL(8), DIMENSION(:,:) :: RES, AYB REAL(8), DIMENSION(:) :: BERR C INTERFACE #include <sunperf.h> void dla_lin_berr (int n, int nz, int nrhs, double *res, double *ayb, double *berr); void dla_lin_berr_64 (long n, long nz, long nrhs, double *res, double *ayb, double *berr);
Oracle Solaris Studio Performance Library dla_lin_berr(3P)
NAME
dla_lin_berr - compute a component-wise relative backward error
SYNOPSIS
SUBROUTINE DLA_LIN_BERR (N, NZ, NRHS, RES, AYB, BERR)
INTEGER N, NZ, NRHS
DOUBLE PRECISION AYB(N,NRHS), BERR(NRHS)
DOUBLE PRECISION RES(N,NRHS)
SUBROUTINE DLA_LIN_BERR_64 (N, NZ, NRHS, RES, AYB, BERR)
INTEGER*8 N, NZ, NRHS
DOUBLE PRECISION AYB(N,NRHS), BERR(NRHS)
DOUBLE PRECISION RES(N,NRHS)
F95 INTERFACE
SUBROUTINE LA_LIN_BERR (N, NZ, NRHS, RES, AYB, BERR)
INTEGER :: N, NZ, NRHS
REAL(8), DIMENSION(:,:) :: RES, AYB
REAL(8), DIMENSION(:) :: BERR
SUBROUTINE LA_LIN_BERR_64 (N, NZ, NRHS, RES, AYB, BERR)
INTEGER(8) :: N, NZ, NRHS
REAL(8), DIMENSION(:,:) :: RES, AYB
REAL(8), DIMENSION(:) :: BERR
C INTERFACE
#include <sunperf.h>
void dla_lin_berr (int n, int nz, int nrhs, double *res, double *ayb,
double *berr);
void dla_lin_berr_64 (long n, long nz, long nrhs, double *res, double
*ayb, double *berr);
PURPOSE
dla_lin_berr computes component-wise relative backward error from the
formula
max(i) (abs(R(i)) / (abs(op(A_s))*abs(Y) + abs(B_s))(i))
where abs(Z) is the component-wise absolute value of the matrix or vec-
tor Z.
ARGUMENTS
N (input)
N is INTEGER
The number of linear equations, i.e., the order of the matrix
A. N >= 0.
NZ (input)
NZ is INTEGER
We add (NZ+1)*SLAMCH( 'Safe minimum' ) to R(i) in the numera-
tor to guard against spuriously zero residuals. Default value
is N.
NRHS (input)
NRHS is INTEGER
The number of right hand sides, i.e., the number of columns
of the matrices AYB, RES, and BERR. NRHS >= 0.
RES (input)
RES is DOUBLE PRECISION array, dimension (N,NRHS) The resid-
ual matrix, i.e., the matrix R in the relative backward error
formula above.
AYB (input)
AYB is DOUBLE PRECISION array, dimension (N, NRHS)
The denominator in the relative backward error formula above,
i.e., the matrix abs(op(A_s))*abs(Y) + abs(B_s). The matrices
A, Y, and B are from iterative refinement (see
dla_gerfsx_extended.f).
BERR (output)
BERR is DOUBLE PRECISION array, dimension (NRHS)
The component-wise relative backward error from the formula
above.
7 Nov 2015 dla_lin_berr(3P)