Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cla_gerfsx_extended (3p)

Name

cla_gerfsx_extended - ear equations by performing extra-precise iterative refinement and pro- vide error bounds and backward error estimates for the solution

Synopsis

SUBROUTINE  CLA_GERFSX_EXTENDED(PREC_TYPE, TRANS_TYPE, N, NRHS, A, LDA,
AF, LDAF, IPIV, COLEQU, C, B, LDB, Y, LDY, BERR_OUT, N_NORMS,
ERRS_N,   ERRS_C,  RES,  AYB,  DY,  Y_TAIL,  RCOND,  ITHRESH,
RTHRESH, DZ_UB, IGNORE_CWISE, INFO)


INTEGER INFO, LDA, LDAF, LDB,  LDY,  N,  NRHS,  PREC_TYPE,  TRANS_TYPE,
N_NORMS

LOGICAL COLEQU, IGNORE_CWISE

INTEGER ITHRESH

REAL RTHRESH, DZ_UB

INTEGER IPIV(*)

COMPLEX   A(LDA,*),   AF(LDAF,*),   B(LDB,*),  Y(LDY,*),  RES(*),DY(*),
Y_TAIL(*)

REAL C(*), AYB(*), RCOND, BERR_OUT(*), ERRS_N(NRHS,*), ERRS_C(NRHS,*)


SUBROUTINE CLA_GERFSX_EXTENDED_64(PREC_TYPE, TRANS_TYPE,  N,  NRHS,  A,
LDA,  AF,  LDAF,  IPIV,  COLEQU, C, B, LDB, Y, LDY, BERR_OUT,
N_NORMS,  ERRS_N,  ERRS_C,  RES,  AYB,  DY,  Y_TAIL,   RCOND,
ITHRESH, RTHRESH, DZ_UB, IGNORE_CWISE, INFO)


INTEGER*8  INFO,  LDA,  LDAF, LDB, LDY, N, NRHS, PREC_TYPE, TRANS_TYPE,
N_NORMS

LOGICAL*8 COLEQU, IGNORE_CWISE

INTEGER*8 ITHRESH

REAL RTHRESH, DZ_UB

INTEGER*8 IPIV(*)

COMPLEX  A(LDA,*),  AF(LDAF,*),   B(LDB,*),   Y(LDY,*),   RES(*),DY(*),
Y_TAIL(*)

REAL C(*), AYB(*), RCOND, BERR_OUT(*), ERRS_N(NRHS,*), ERRS_C(NRHS,*)


F95 INTERFACE
SUBROUTINE  LA_GERFSX_EXTENDED(PREC_TYPE,  TRANS_TYPE, N, NRHS, A, LDA,
AF, LDAF, IPIV, COLEQU, C, B, LDB, Y, LDY, BERR_OUT, N_NORMS,
ERRS_N,   ERRS_C,  RES,  AYB,  DY,  Y_TAIL,  RCOND,  ITHRESH,
RTHRESH, DZ_UB, IGNORE_CWISE, INFO)


REAL, DIMENSION(:,:) :: ERRS_N, ERRS_C

INTEGER ::  PREC_TYPE,  TRANS_TYPE,  N,  NRHS,  LDA,  LDAF,  LDB,  LDY,
N_NORMS, ITHRESH, INFO

LOGICAL :: COLEQU, IGNORE_CWISE

INTEGER, DIMENSION(:) :: IPIV

REAL, DIMENSION(:) :: C, BERR_OUT, AYB

REAL :: RCOND, RTHRESH, DZ_UB

COMPLEX, DIMENSION(:) :: RES, DY, Y_TAIL

COMPLEX, DIMENSION(:,:) :: A, AF, B, Y


SUBROUTINE  LA_GERFSX_EXTENDED_64(PREC_TYPE,  TRANS_TYPE,  N,  NRHS, A,
LDA, AF, LDAF, IPIV, COLEQU, C, B,  LDB,  Y,  LDY,  BERR_OUT,
N_NORMS,   ERRS_N,  ERRS_C,  RES,  AYB,  DY,  Y_TAIL,  RCOND,
ITHRESH, RTHRESH, DZ_UB, IGNORE_CWISE, INFO)


REAL, DIMENSION(:,:) :: ERRS_N, ERRS_C

INTEGER(8) :: PREC_TYPE, TRANS_TYPE, N,  NRHS,  LDA,  LDAF,  LDB,  LDY,
N_NORMS, ITHRESH, INFO

LOGICAL(8) :: COLEQU, IGNORE_CWISE

INTEGER(8), DIMENSION(:) :: IPIV

REAL, DIMENSION(:) :: C, BERR_OUT, AYB

REAL :: RCOND, RTHRESH, DZ_UB

COMPLEX, DIMENSION(:) :: RES, DY, Y_TAIL

COMPLEX, DIMENSION(:,:) :: A, AF, B, Y


C INTERFACE
#include <sunperf.h>

void  cla_gerfsx_extended  (int  prec_type,  int trans_type, int n, int
nrhs, floatcomplex *a, int lda, floatcomplex *af,  int  ldaf,
int  *ipiv,  int  colequ, float *c, floatcomplex *b, int ldb,
floatcomplex *y, int ldy, float *berr_out, int n_norms, float
*errs_n,  float  *errs_c,  float  rcond,  int  ithresh, float
rthresh, float dz_ub, int ignore_cwise, int *info);


void cla_gerfsx_extended_64 (long prec_type, long trans_type,  long  n,
long  nrhs, floatcomplex *a, long lda, floatcomplex *af, long
ldaf, long *ipiv, long colequ,  float  *c,  floatcomplex  *b,
long  ldb,  floatcomplex  *y, long ldy, float *berr_out, long
n_norms, float *errs_n,  float  *errs_c,  float  rcond,  long
ithresh,  float rthresh, float dz_ub, long ignore_cwise, long
*info);

Description

Oracle Solaris Studio Performance Library              cla_gerfsx_extended(3P)



NAME
       cla_gerfsx_extended - improve the computed solution to a system of lin-
       ear equations by performing extra-precise iterative refinement and pro-
       vide error bounds and backward error estimates for the solution


SYNOPSIS
       SUBROUTINE  CLA_GERFSX_EXTENDED(PREC_TYPE, TRANS_TYPE, N, NRHS, A, LDA,
                 AF, LDAF, IPIV, COLEQU, C, B, LDB, Y, LDY, BERR_OUT, N_NORMS,
                 ERRS_N,   ERRS_C,  RES,  AYB,  DY,  Y_TAIL,  RCOND,  ITHRESH,
                 RTHRESH, DZ_UB, IGNORE_CWISE, INFO)


       INTEGER INFO, LDA, LDAF, LDB,  LDY,  N,  NRHS,  PREC_TYPE,  TRANS_TYPE,
                 N_NORMS

       LOGICAL COLEQU, IGNORE_CWISE

       INTEGER ITHRESH

       REAL RTHRESH, DZ_UB

       INTEGER IPIV(*)

       COMPLEX   A(LDA,*),   AF(LDAF,*),   B(LDB,*),  Y(LDY,*),  RES(*),DY(*),
                 Y_TAIL(*)

       REAL C(*), AYB(*), RCOND, BERR_OUT(*), ERRS_N(NRHS,*), ERRS_C(NRHS,*)


       SUBROUTINE CLA_GERFSX_EXTENDED_64(PREC_TYPE, TRANS_TYPE,  N,  NRHS,  A,
                 LDA,  AF,  LDAF,  IPIV,  COLEQU, C, B, LDB, Y, LDY, BERR_OUT,
                 N_NORMS,  ERRS_N,  ERRS_C,  RES,  AYB,  DY,  Y_TAIL,   RCOND,
                 ITHRESH, RTHRESH, DZ_UB, IGNORE_CWISE, INFO)


       INTEGER*8  INFO,  LDA,  LDAF, LDB, LDY, N, NRHS, PREC_TYPE, TRANS_TYPE,
                 N_NORMS

       LOGICAL*8 COLEQU, IGNORE_CWISE

       INTEGER*8 ITHRESH

       REAL RTHRESH, DZ_UB

       INTEGER*8 IPIV(*)

       COMPLEX  A(LDA,*),  AF(LDAF,*),   B(LDB,*),   Y(LDY,*),   RES(*),DY(*),
                 Y_TAIL(*)

       REAL C(*), AYB(*), RCOND, BERR_OUT(*), ERRS_N(NRHS,*), ERRS_C(NRHS,*)


   F95 INTERFACE
       SUBROUTINE  LA_GERFSX_EXTENDED(PREC_TYPE,  TRANS_TYPE, N, NRHS, A, LDA,
                 AF, LDAF, IPIV, COLEQU, C, B, LDB, Y, LDY, BERR_OUT, N_NORMS,
                 ERRS_N,   ERRS_C,  RES,  AYB,  DY,  Y_TAIL,  RCOND,  ITHRESH,
                 RTHRESH, DZ_UB, IGNORE_CWISE, INFO)


       REAL, DIMENSION(:,:) :: ERRS_N, ERRS_C

       INTEGER ::  PREC_TYPE,  TRANS_TYPE,  N,  NRHS,  LDA,  LDAF,  LDB,  LDY,
                 N_NORMS, ITHRESH, INFO

       LOGICAL :: COLEQU, IGNORE_CWISE

       INTEGER, DIMENSION(:) :: IPIV

       REAL, DIMENSION(:) :: C, BERR_OUT, AYB

       REAL :: RCOND, RTHRESH, DZ_UB

       COMPLEX, DIMENSION(:) :: RES, DY, Y_TAIL

       COMPLEX, DIMENSION(:,:) :: A, AF, B, Y


       SUBROUTINE  LA_GERFSX_EXTENDED_64(PREC_TYPE,  TRANS_TYPE,  N,  NRHS, A,
                 LDA, AF, LDAF, IPIV, COLEQU, C, B,  LDB,  Y,  LDY,  BERR_OUT,
                 N_NORMS,   ERRS_N,  ERRS_C,  RES,  AYB,  DY,  Y_TAIL,  RCOND,
                 ITHRESH, RTHRESH, DZ_UB, IGNORE_CWISE, INFO)


       REAL, DIMENSION(:,:) :: ERRS_N, ERRS_C

       INTEGER(8) :: PREC_TYPE, TRANS_TYPE, N,  NRHS,  LDA,  LDAF,  LDB,  LDY,
                 N_NORMS, ITHRESH, INFO

       LOGICAL(8) :: COLEQU, IGNORE_CWISE

       INTEGER(8), DIMENSION(:) :: IPIV

       REAL, DIMENSION(:) :: C, BERR_OUT, AYB

       REAL :: RCOND, RTHRESH, DZ_UB

       COMPLEX, DIMENSION(:) :: RES, DY, Y_TAIL

       COMPLEX, DIMENSION(:,:) :: A, AF, B, Y


   C INTERFACE
       #include <sunperf.h>

       void  cla_gerfsx_extended  (int  prec_type,  int trans_type, int n, int
                 nrhs, floatcomplex *a, int lda, floatcomplex *af,  int  ldaf,
                 int  *ipiv,  int  colequ, float *c, floatcomplex *b, int ldb,
                 floatcomplex *y, int ldy, float *berr_out, int n_norms, float
                 *errs_n,  float  *errs_c,  float  rcond,  int  ithresh, float
                 rthresh, float dz_ub, int ignore_cwise, int *info);


       void cla_gerfsx_extended_64 (long prec_type, long trans_type,  long  n,
                 long  nrhs, floatcomplex *a, long lda, floatcomplex *af, long
                 ldaf, long *ipiv, long colequ,  float  *c,  floatcomplex  *b,
                 long  ldb,  floatcomplex  *y, long ldy, float *berr_out, long
                 n_norms, float *errs_n,  float  *errs_c,  float  rcond,  long
                 ithresh,  float rthresh, float dz_ub, long ignore_cwise, long
                 *info);


PURPOSE
       cla_gerfsx_extended improves the computed solution to a system of  lin-
       ear equations by performing extra-precise iterative refinement and pro-
       vides error bounds and backward error estimates for the solution.  This
       subroutine  is  called  by CGERFSX to perform iterative refinement.  In
       addition to normwise error bound, the code provides maximum  component-
       wise  error  bound  if possible. See comments for ERRS_N and ERRS_C for
       details of the error bounds. Note that this subroutine is only resonsi-
       ble for setting the second fields of ERRS_N and ERRS_C.


ARGUMENTS
       PREC_TYPE (input)
                 PREC_TYPE is INTEGER
                 Specifies  the  intermediate  precision to be used in refine-
                 ment.  The value is defined by ILAPREC(P) where P is a  CHAR-
                 ACTER and
                 P    = 'S':  Single
                 = 'D':  Double
                 = 'I':  Indigenous
                 = 'X', 'E':  Extra


       TRANS_TYPE (input)
                 TRANS_TYPE is INTEGER
                 Specifies  the  transposition  operation  on A.  The value is
                 defined by ILATRANS(T) where T is a CHARACTER and
                 T    = 'N':  No transpose
                 = 'T':  Transpose
                 = 'C':  Conjugate transpose


       N (input)
                 N is INTEGER
                 The number of linear equations, i.e., the order of the matrix
                 A. N >= 0.


       NRHS (input)
                 NRHS is INTEGER
                 The  number  of right-hand-sides, i.e., the number of columns
                 of the matrix B.


       A (input)
                 A is COMPLEX array, dimension (LDA,N)
                 On entry, the N-by-N matrix A.


       LDA (input)
                 LDA is INTEGER
                 The leading dimension of the array A.
                 LDA >= max(1,N).


       AF (input)
                 AF is COMPLEX array, dimension (LDAF,N)
                 The factors L and U from the factorization  A=P*L*U  as  com-
                 puted by CGETRF.


       LDAF (input)
                 LDAF is INTEGER
                 The leading dimension of the array AF.
                 LDAF >= max(1,N).


       IPIV (input)
                 IPIV is INTEGER array, dimension (N)
                 The  pivot indices from the factorization A=P*L*U as computed
                 by CGETRF; row i of the  matrix  was  interchanged  with  row
                 IPIV(i).


       COLEQU (input)
                 COLEQU is LOGICAL
                 If  .TRUE.  then  column  equilibration  was done to A before
                 calling this routine. This is needed to compute the  solution
                 and error bounds correctly.


       C (input)
                 C is REAL array, dimension (N)
                 The column scale factors for A. If COLEQU = .FALSE., C is not
                 accessed. If C is input, each element of C should be a  power
                 of  the  radix  to ensure a reliable solution and error esti-
                 mates.  Scaling by powers of the radix does not cause  round-
                 ing  errors unless the result underflows or overflows. Round-
                 ing errors during scaling lead to refining with a matrix that
                 is  not equivalent to the input matrix, producing error esti-
                 mates that may not be reliable.


       B (input)
                 B is COMPLEX array, dimension (LDB,NRHS)
                 The right-hand-side matrix B.


       LDB (input)
                 LDB is INTEGER
                 The leading dimension of the array B.
                 LDB >= max(1,N).


       Y (input/output)
                 Y is COMPLEX array, dimension (LDY,NRHS)
                 On entry, the solution matrix X, as computed by CGETRS.
                 On exit, the improved solution matrix Y.


       LDY (input)
                 LDY is INTEGER
                 The leading dimension of the array Y.
                 LDY >= max(1,N).


       BERR_OUT (output)
                 BERR_OUT is REAL array, dimension (NRHS)
                 On exit,  BERR_OUT(j)  contains  the  componentwise  relative
                 backward error for right-hand-side j from the formula
                 max(i)(abs(RES(i))/(abs(op(A_s))*abs(Y)+abs(B_s))(i))
                 where  abs(Z)  is  the  componentwise  absolute  value of the
                 matrix or vector Z. This is computed by CLA_LIN_BERR.


       N_NORMS (input)
                 N_NORMS is INTEGER
                 Determines which error  bounds  to  return  (see  ERRS_N  and
                 ERRS_C).
                 If N_NORMS >= 1 return normwise error bounds.
                 If N_NORMS >= 2 return componentwise error bounds.


       ERRS_N (input/output)
                 ERRS_N is REAL array, dimension (NRHS, N_NORMS)
                 For  each  right-hand  side,  this array contains information
                 about various error bounds and condition numbers  correspond-
                 ing  to the normwise relative error, which is defined as fol-
                 lows: Normwise relative error in the ith solution vector:

                 max_j (abs(XTRUE(j,i) - X(j,i)))
                 ------------------------------
                        max_j abs(X(j,i))

                 The array is indexed by the  type  of  error  information  as
                 described  below.  There  currently are up to three pieces of
                 information returned.
                 The first index in ERRS_N(i,:) corresponds to the ith  right-
                 hand side.
                 The  second  index  in  ERRS_N(:,err)  contains the following
                 three fields:
                 err = 1 "Trust/don't trust" boolean. Trust the answer if  the
                 reciprocal  condition  number  is  less  than  the  threshold
                 sqrt(n) * slamch('Epsilon').
                 err = 2  "Guaranteed"  error  bound:  The  estimated  forward
                 error,  almost  certainly  within  a factor of 10 of the true
                 error so long as the next entry is greater than the threshold
                 sqrt(n)  * slamch('Epsilon'). This error bound should only be
                 trusted if the previous boolean is true.
                 err = 3   Reciprocal  condition  number:  Estimated  normwise
                 reciprocal  condition  number.   Compared  with the threshold
                 sqrt(n) * slamch('Epsilon') to determine if the  error  esti-
                 mate  is "guaranteed". These reciprocal condition numbers are
                 1/(norm(Z^{-1},inf)*norm(Z,inf))   for   some   appropriately
                 scaled matrix Z.
                 Let  Z = S*A, where S scales each row by a power of the radix
                 so all absolute row sums of Z are approximately 1.
                 This subroutine is only responsible for  setting  the  second
                 field above.
                 See  Lapack  Working  Note  165 for further details and extra
                 cautions.


       ERRS_C (input/output)
                 ERRS_C is REAL array, dimension (NRHS, N_NORMS)
                 For each right-hand side,  this  array  contains  information
                 about  various error bounds and condition numbers correspond-
                 ing to the componentwise relative error, which is defined  as
                 follows:  Componentwise  relative  error  in the ith solution
                 vector:

                        abs(XTRUE(j,i) - X(j,i))
                 max_j ----------------------
                             abs(X(j,i))

                 The array is indexed by the right-hand side i (on  which  the
                 componentwise  relative error depends), and the type of error
                 information as described below. There  currently  are  up  to
                 three  pieces  of  information  returned  for each right-hand
                 side. If componentwise accuracy is not requested (PARAMS(3) =
                 0.0), then ERRS_C is not accessed. If N_NORMS .LT. 3, then at
                 most the first (:,N_NORMS) entries are returned.
                 The first index in ERRS_C(i,:) corresponds to the ith  right-
                 hand side.
                 The  second  index  in  ERRS_C(:,err)  contains the following
                 three fields:
                 err = 1 "Trust/don't trust" boolean. Trust the answer if  the
                 reciprocal  condition  number  is  less  than  the  threshold
                 sqrt(n) * slamch('Epsilon').
                 err = 2  "Guaranteed"  error  bound:  The  estimated  forward
                 error,  almost  certainly  within  a factor of 10 of the true
                 error so long as the next entry is greater than the threshold
                 sqrt(n)  * slamch('Epsilon'). This error bound should only be
                 trusted if the previous boolean is true.
                 err = 3  Reciprocal condition number: Estimated componentwise
                 reciprocal  condition  number.   Compared  with the threshold
                 sqrt(n) * slamch('Epsilon') to determine if the  error  esti-
                 mate  is "guaranteed". These reciprocal condition numbers are
                 1 / (norm(Z^{-1},inf) * norm(Z,inf)) for  some  appropriately
                 scaled matrix Z.
                 Let  Z  = S*(A*diag(x)), where x is the solution for the cur-
                 rent right-hand side and S scales each row of A*diag(x) by  a
                 power of the radix so all absolute row sums of Z are approxi-
                 mately 1.
                 This subroutine is only responsible for  setting  the  second
                 field above.  See Lapack Working Note 165 for further details
                 and extra cautions.


       RES (input)
                 RES is COMPLEX array, dimension (N)
                 Workspace to hold the intermediate residual.


       AYB (input)
                 AYB is REAL array, dimension (N)
                 Workspace.


       DY (input)
                 DY is COMPLEX array, dimension (N)
                 Workspace to hold the intermediate solution.


       Y_TAIL (input)
                 Y_TAIL is COMPLEX array, dimension (N)
                 Workspace to hold the trailing bits of the intermediate solu-
                 tion.


       RCOND (input)
                 RCOND is REAL
                 Reciprocal  scaled  condition  number. This is an estimate of
                 the reciprocal Skeel condition number of the matrix  A  after
                 equilibration  (if  done).  If  this is less than the machine
                 precision (in particular, if it is zero), the matrix is  sin-
                 gular to working precision.  Note that the error may still be
                 small even if this  number  is  very  small  and  the  matrix
                 appears ill- conditioned.


       ITHRESH (input)
                 ITHRESH is INTEGER
                 The  maximum  number  of  residual  computations  allowed for
                 refinement. The default is 10. For 'aggressive' set to 100 to
                 permit  convergence  using approximate factorizations or fac-
                 torizations other than LU. If the factorization uses a  tech-
                 nique  other  than  Gaussian  elimination,  the guarantees in
                 ERRS_N and ERRS_C may no longer be trustworthy.


       RTHRESH (input)
                 RTHRESH is REAL
                 Determines when to stop  refinement  if  the  error  estimate
                 stops decreasing. Refinement will stop when the next solution
                 no longer satisfies norm(dx_{i+1})  <  RTHRESH  *  norm(dx_i)
                 where  norm(Z) is the infinity norm of Z. RTHRESH satisfies 0
                 < RTHRESH <= 1. The default value is  0.5.  For  'aggressive'
                 set to 0.9 to permit convergence on extremely ill-conditioned
                 matrices. See LAWN 165 for more details.


       DZ_UB (input)
                 DZ_UB is REAL
                 Determines when to start  considering  componentwise  conver-
                 gence.   Componentwise  convergence  is only considered after
                 each component of the solution Y is stable, which we  definte
                 as  the  relative  change  in  each component being less than
                 DZ_UB. The default value is 0.25, requiring the first bit  to
                 be stable. See LAWN 165 for more details.


       IGNORE_CWISE (input)
                 IGNORE_CWISE is LOGICAL
                 If  .TRUE.  then  ignore  componentwise  convergence. Default
                 value is .FALSE..


       INFO (output)
                 INFO is INTEGER
                 = 0:  Successful exit.
                 < 0:  if INFO = -i, the ith argument to CGETRS had an illegal
                 value




                                  7 Nov 2015           cla_gerfsx_extended(3P)