Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

chetrs_rook (3p)

Name

chetrs_rook - compute the solution to a system of linear equations A*X=B for Hermitian matrices using factorization obtained with one of the bounded diagonal pivoting methods (max 2 interchanges)

Synopsis

SUBROUTINE CHETRS_ROOK(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)


CHARACTER*1 UPLO

INTEGER INFO, LDA, LDB, N, NRHS

INTEGER IPIV(*)

COMPLEX A(LDA,*), B(LDB,*)


SUBROUTINE CHETRS_ROOK_64(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)


CHARACTER*1 UPLO

INTEGER*8 INFO, LDA, LDB, N, NRHS

INTEGER*8 IPIV(*)

COMPLEX A(LDA,*), B(LDB,*)


F95 INTERFACE
SUBROUTINE HETRS_ROOK(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)


INTEGER :: N, NRHS, LDA, LDB, INFO

CHARACTER(LEN=1) :: UPLO

INTEGER, DIMENSION(:) :: IPIV

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


SUBROUTINE HETRS_ROOK_64(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)


INTEGER(8) :: N, NRHS, LDA, LDB, INFO

CHARACTER(LEN=1) :: UPLO

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

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


C INTERFACE
#include <sunperf.h>

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


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

Description

Oracle Solaris Studio Performance Library                      chetrs_rook(3P)



NAME
       chetrs_rook  -  compute  the  solution  to a system of linear equations
       A*X=B for Hermitian matrices using factorization obtained with  one  of
       the bounded diagonal pivoting methods (max 2 interchanges)


SYNOPSIS
       SUBROUTINE CHETRS_ROOK(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)


       CHARACTER*1 UPLO

       INTEGER INFO, LDA, LDB, N, NRHS

       INTEGER IPIV(*)

       COMPLEX A(LDA,*), B(LDB,*)


       SUBROUTINE CHETRS_ROOK_64(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)


       CHARACTER*1 UPLO

       INTEGER*8 INFO, LDA, LDB, N, NRHS

       INTEGER*8 IPIV(*)

       COMPLEX A(LDA,*), B(LDB,*)


   F95 INTERFACE
       SUBROUTINE HETRS_ROOK(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)


       INTEGER :: N, NRHS, LDA, LDB, INFO

       CHARACTER(LEN=1) :: UPLO

       INTEGER, DIMENSION(:) :: IPIV

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


       SUBROUTINE HETRS_ROOK_64(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)


       INTEGER(8) :: N, NRHS, LDA, LDB, INFO

       CHARACTER(LEN=1) :: UPLO

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

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


   C INTERFACE
       #include <sunperf.h>

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


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


PURPOSE
       chetrs_rook solves a system of linear equations A*X = B with a  complex
       Hermitian matrix A using the factorization A = U*D*U**H or A = L*D*L**H
       computed by CHETRF_ROOK.


ARGUMENTS
       UPLO (input)
                 UPLO is CHARACTER*1
                 Specifies whether the details of the factorization are stored
                 as an upper or lower triangular matrix.
                 = 'U':  Upper triangular, form is A = U*D*U**H;
                 = 'L':  Lower triangular, form is A = L*D*L**H.


       N (input)
                 N is INTEGER
                 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. NRHS >= 0.


       A (input)
                 A is COMPLEX array, dimension (LDA,N)
                 The block diagonal matrix  D  and  the  multipliers  used  to
                 obtain the factor U or L as computed by CHETRF_ROOK.


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


       IPIV (input)
                 IPIV is INTEGER array, dimension (N)
                 Details  of  the interchanges and the block structure of D as
                 determined by CHETRF_ROOK.


       B (input/output)
                 B is COMPLEX array, dimension (LDB,NRHS)
                 On entry, the right hand side matrix B.
                 On exit, the solution matrix X.


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


       INFO (output)
                 INFO is INTEGER
                 = 0:  successful exit;
                 < 0:  if INFO = -i, the i-th argument had an illegal value.




                                  7 Nov 2015                   chetrs_rook(3P)