csytrf


NAME

csytrf - compute the factorization of a complex symmetric matrix A using the Bunch-Kaufman diagonal pivoting method


SYNOPSIS

  SUBROUTINE CSYTRF( UPLO, N, A, LDA, IPIVOT, WORK, LDWORK, INFO)
  CHARACTER * 1 UPLO
  COMPLEX A(LDA,*), WORK(*)
  INTEGER N, LDA, LDWORK, INFO
  INTEGER IPIVOT(*)
 
  SUBROUTINE CSYTRF_64( UPLO, N, A, LDA, IPIVOT, WORK, LDWORK, INFO)
  CHARACTER * 1 UPLO
  COMPLEX A(LDA,*), WORK(*)
  INTEGER*8 N, LDA, LDWORK, INFO
  INTEGER*8 IPIVOT(*)
 

F95 INTERFACE

  SUBROUTINE SYTRF( UPLO, [N], A, [LDA], IPIVOT, [WORK], [LDWORK], 
 *       [INFO])
  CHARACTER(LEN=1) :: UPLO
  COMPLEX, DIMENSION(:) :: WORK
  COMPLEX, DIMENSION(:,:) :: A
  INTEGER :: N, LDA, LDWORK, INFO
  INTEGER, DIMENSION(:) :: IPIVOT
 
  SUBROUTINE SYTRF_64( UPLO, [N], A, [LDA], IPIVOT, [WORK], [LDWORK], 
 *       [INFO])
  CHARACTER(LEN=1) :: UPLO
  COMPLEX, DIMENSION(:) :: WORK
  COMPLEX, DIMENSION(:,:) :: A
  INTEGER(8) :: N, LDA, LDWORK, INFO
  INTEGER(8), DIMENSION(:) :: IPIVOT
 

C INTERFACE

#include <sunperf.h>

void csytrf(char uplo, int n, complex *a, int lda, int *ipivot, int *info);

void csytrf_64(char uplo, long n, complex *a, long lda, long *ipivot, long *info);


PURPOSE

csytrf computes the factorization of a complex symmetric matrix A using the Bunch-Kaufman diagonal pivoting method. The form of the factorization is

   A = U*D*U**T  or  A = L*D*L**T

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

This is the blocked version of the algorithm, calling Level 3 BLAS.


ARGUMENTS

* UPLO (input)
* N (input)
The order of the matrix A. N >= 0.

* A (input/output)
On entry, the symmetric matrix A. If UPLO = 'U', the leading N-by-N upper triangular part of A contains the upper triangular part of the matrix A, and the strictly lower triangular part of A is not referenced. If UPLO = 'L', the leading N-by-N lower triangular part of A contains the lower triangular part of the matrix A, and the strictly upper triangular part of A is not referenced.

On exit, the block diagonal matrix D and the multipliers used to obtain the factor U or L (see below for further details).

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

* IPIVOT (output)
Details of the interchanges and the block structure of D. If IPIVOT(k) > 0, then rows and columns k and IPIVOT(k) were interchanged and D(k,k) is a 1-by-1 diagonal block. If UPLO = 'U' and IPIVOT(k) = IPIVOT(k-1) < 0, then rows and columns k-1 and -IPIVOT(k) were interchanged and D(k-1:k,k-1:k) is a 2-by-2 diagonal block. If UPLO = 'L' and IPIVOT(k) = IPIVOT(k+1) < 0, then rows and columns k+1 and -IPIVOT(k) were interchanged and D(k:k+1,k:k+1) is a 2-by-2 diagonal block.

* WORK (workspace)
On exit, if INFO = 0, WORK(1) returns the optimal LDWORK.

* LDWORK (input)
The length of WORK. LDWORK >=1. For best performance LDWORK >= N*NB, where NB is the block size returned by ILAENV.

If LDWORK = -1, then a workspace query is assumed; the routine only calculates the optimal size of the WORK array, returns this value as the first entry of the WORK array, and no error message related to LDWORK is issued by XERBLA.

* INFO (output)