Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dsytrs2 (3p)

Name

dsytrs2 - metric matrix A using the factorization computed by DSYTRF and con- verted by DSYCONV

Synopsis

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


CHARACTER*1 UPLO

INTEGER INFO, LDA, LDB, N, NRHS

INTEGER IPIV(*)

DOUBLE PRECISION A(LDA,*), B(LDB,*), WORK(*)


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


CHARACTER*1 UPLO

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

INTEGER*8 IPIV(*)

DOUBLE PRECISION A(LDA,*), B(LDB,*), WORK(*)


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


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

CHARACTER(LEN=1) :: UPLO

INTEGER, DIMENSION(:) :: IPIV

REAL(8), DIMENSION(:,:) :: A, B

REAL(8), DIMENSION(:) :: WORK


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


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

CHARACTER(LEN=1) :: UPLO

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

REAL(8), DIMENSION(:,:) :: A, B

REAL(8), DIMENSION(:) :: WORK


C INTERFACE
#include <sunperf.h>

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


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

Description

Oracle Solaris Studio Performance Library                          dsytrs2(3P)



NAME
       dsytrs2  -  solve a system of linear equations A*X = B with a real sym-
       metric matrix A using the factorization computed  by  DSYTRF  and  con-
       verted by DSYCONV


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


       CHARACTER*1 UPLO

       INTEGER INFO, LDA, LDB, N, NRHS

       INTEGER IPIV(*)

       DOUBLE PRECISION A(LDA,*), B(LDB,*), WORK(*)


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


       CHARACTER*1 UPLO

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

       INTEGER*8 IPIV(*)

       DOUBLE PRECISION A(LDA,*), B(LDB,*), WORK(*)


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


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

       CHARACTER(LEN=1) :: UPLO

       INTEGER, DIMENSION(:) :: IPIV

       REAL(8), DIMENSION(:,:) :: A, B

       REAL(8), DIMENSION(:) :: WORK


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


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

       CHARACTER(LEN=1) :: UPLO

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

       REAL(8), DIMENSION(:,:) :: A, B

       REAL(8), DIMENSION(:) :: WORK


   C INTERFACE
       #include <sunperf.h>

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


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


PURPOSE
       dsytrs2 solves a system of linear equations A*X = B with a real symmet-
       ric matrix A using the factorization A = U*D*U**T or A = L*D*L**T  com-
       puted by DSYTRF and converted by DSYCONV.


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**T;
                 = 'L':  Lower triangular, form is A = L*D*L**T.


       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 DOUBLE PRECISION array, dimension (LDA,N)
                 The  block  diagonal  matrix  D  and  the multipliers used to
                 obtain the factor U or L as computed by DSYTRF.


       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 DSYTRF.


       B (input/output)
                 B is DOUBLE PRECISION 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).


       WORK (output)
                 WORK is REAL array, dimension (N)


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



                                  7 Nov 2015                       dsytrs2(3P)