NAME

csysv - compute the solution to a complex system of linear equations A * X = B,


SYNOPSIS

  SUBROUTINE CSYSV( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, 
 *      INFO)
  CHARACTER * 1 UPLO
  COMPLEX A(LDA,*), B(LDB,*), WORK(*)
  INTEGER N, NRHS, LDA, LDB, LWORK, INFO
  INTEGER IPIV(*)
  SUBROUTINE CSYSV_64( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, 
 *      LWORK, INFO)
  CHARACTER * 1 UPLO
  COMPLEX A(LDA,*), B(LDB,*), WORK(*)
  INTEGER*8 N, NRHS, LDA, LDB, LWORK, INFO
  INTEGER*8 IPIV(*)

F95 INTERFACE

  SUBROUTINE SYSV( UPLO, [N], [NRHS], A, [LDA], IPIV, B, [LDB], [WORK], 
 *       [LWORK], [INFO])
  CHARACTER(LEN=1) :: UPLO
  COMPLEX, DIMENSION(:) :: WORK
  COMPLEX, DIMENSION(:,:) :: A, B
  INTEGER :: N, NRHS, LDA, LDB, LWORK, INFO
  INTEGER, DIMENSION(:) :: IPIV
  SUBROUTINE SYSV_64( UPLO, [N], [NRHS], A, [LDA], IPIV, B, [LDB], 
 *       [WORK], [LWORK], [INFO])
  CHARACTER(LEN=1) :: UPLO
  COMPLEX, DIMENSION(:) :: WORK
  COMPLEX, DIMENSION(:,:) :: A, B
  INTEGER(8) :: N, NRHS, LDA, LDB, LWORK, INFO
  INTEGER(8), DIMENSION(:) :: IPIV

C INTERFACE

#include <sunperf.h>

void csysv(char uplo, int n, int nrhs, complex *a, int lda, int *ipiv, complex *b, int ldb, int *info);

void csysv_64(char uplo, long n, long nrhs, complex *a, long lda, long *ipiv, complex *b, long ldb, long *info);


PURPOSE

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

The diagonal pivoting method is used to factor A as

   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. The factored form of A is then used to solve the system of equations A * X = B.


ARGUMENTS