NAME

zsysvx - use the diagonal pivoting factorization to compute the solution to a complex system of linear equations A * X = B,


SYNOPSIS

  SUBROUTINE ZSYSVX( FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIVOT, B, 
 *      LDB, X, LDX, RCOND, FERR, BERR, WORK, LDWORK, WORK2, INFO)
  CHARACTER * 1 FACT, UPLO
  DOUBLE COMPLEX A(LDA,*), AF(LDAF,*), B(LDB,*), X(LDX,*), WORK(*)
  INTEGER N, NRHS, LDA, LDAF, LDB, LDX, LDWORK, INFO
  INTEGER IPIVOT(*)
  DOUBLE PRECISION RCOND
  DOUBLE PRECISION FERR(*), BERR(*), WORK2(*)
  SUBROUTINE ZSYSVX_64( FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIVOT, 
 *      B, LDB, X, LDX, RCOND, FERR, BERR, WORK, LDWORK, WORK2, INFO)
  CHARACTER * 1 FACT, UPLO
  DOUBLE COMPLEX A(LDA,*), AF(LDAF,*), B(LDB,*), X(LDX,*), WORK(*)
  INTEGER*8 N, NRHS, LDA, LDAF, LDB, LDX, LDWORK, INFO
  INTEGER*8 IPIVOT(*)
  DOUBLE PRECISION RCOND
  DOUBLE PRECISION FERR(*), BERR(*), WORK2(*)

F95 INTERFACE

  SUBROUTINE SYSVX( FACT, UPLO, [N], [NRHS], A, [LDA], AF, [LDAF], 
 *       IPIVOT, B, [LDB], X, [LDX], RCOND, FERR, BERR, [WORK], [LDWORK], 
 *       [WORK2], [INFO])
  CHARACTER(LEN=1) :: FACT, UPLO
  COMPLEX(8), DIMENSION(:) :: WORK
  COMPLEX(8), DIMENSION(:,:) :: A, AF, B, X
  INTEGER :: N, NRHS, LDA, LDAF, LDB, LDX, LDWORK, INFO
  INTEGER, DIMENSION(:) :: IPIVOT
  REAL(8) :: RCOND
  REAL(8), DIMENSION(:) :: FERR, BERR, WORK2
  SUBROUTINE SYSVX_64( FACT, UPLO, [N], [NRHS], A, [LDA], AF, [LDAF], 
 *       IPIVOT, B, [LDB], X, [LDX], RCOND, FERR, BERR, [WORK], [LDWORK], 
 *       [WORK2], [INFO])
  CHARACTER(LEN=1) :: FACT, UPLO
  COMPLEX(8), DIMENSION(:) :: WORK
  COMPLEX(8), DIMENSION(:,:) :: A, AF, B, X
  INTEGER(8) :: N, NRHS, LDA, LDAF, LDB, LDX, LDWORK, INFO
  INTEGER(8), DIMENSION(:) :: IPIVOT
  REAL(8) :: RCOND
  REAL(8), DIMENSION(:) :: FERR, BERR, WORK2

C INTERFACE

#include <sunperf.h>

void zsysvx(char fact, char uplo, int n, int nrhs, doublecomplex *a, int lda, doublecomplex *af, int ldaf, int *ipivot, doublecomplex *b, int ldb, doublecomplex *x, int ldx, double *rcond, double *ferr, double *berr, int *info);

void zsysvx_64(char fact, char uplo, long n, long nrhs, doublecomplex *a, long lda, doublecomplex *af, long ldaf, long *ipivot, doublecomplex *b, long ldb, doublecomplex *x, long ldx, double *rcond, double *ferr, double *berr, long *info);


PURPOSE

zsysvx uses the diagonal pivoting factorization to compute the solution to a complex system of linear equations A * X = B, where A is an N-by-N symmetric matrix and X and B are N-by-NRHS matrices.

Error bounds on the solution and a condition estimate are also provided.

The following steps are performed:

1. If FACT = 'N', the diagonal pivoting method is used to factor A. The form of the factorization is

      A = U * D * U**T,  if UPLO = 'U', or
      A = L * D * L**T,  if UPLO = 'L',
   where U (or L) is a product of permutation and unit upper (lower)
   triangular matrices, and D is symmetric and block diagonal with
   1-by-1 and 2-by-2 diagonal blocks.

2. If some D(i,i)=0, so that D is exactly singular, then the routine returns with INFO = i. Otherwise, the factored form of A is used to estimate the condition number of the matrix A. If the reciprocal of the condition number is less than machine precision, INFO = N+1 is returned as a warning, but the routine still goes on to solve for X and compute error bounds as described below.

3. The system of equations is solved for X using the factored form of A.

4. Iterative refinement is applied to improve the computed solution matrix and calculate error bounds and backward error estimates for it.


ARGUMENTS