Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dsyconv (3p)

Name

dsyconv - versa

Synopsis

SUBROUTINE DSYCONV(UPLO, WAY, N, A, LDA, IPIV, WORK, INFO)


CHARACTER*1 UPLO, WAY

INTEGER INFO, LDA, N

INTEGER IPIV(*)

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


SUBROUTINE DSYCONV_64(UPLO, WAY, N, A, LDA, IPIV, WORK, INFO)


CHARACTER*1 UPLO, WAY

INTEGER*8 INFO, LDA, N

INTEGER*8 IPIV(*)

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


F95 INTERFACE
SUBROUTINE SYCONV(UPLO, WAY, N, A, LDA, IPIV, WORK, INFO)


INTEGER :: N, LDA, INFO

CHARACTER(LEN=1) :: UPLO, WAY

INTEGER, DIMENSION(:) :: IPIV

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

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


SUBROUTINE SYCONV_64(UPLO, WAY, N, A, LDA, IPIV, WORK, INFO)


INTEGER(8) :: N, LDA, INFO

CHARACTER(LEN=1) :: UPLO, WAY

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

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

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


C INTERFACE
#include <sunperf.h>

void  dsyconv  (char  uplo,  char  way,  int n, double *a, int lda, int
*ipiv, int *info);


void dsyconv_64 (char uplo, char way, long n, double *a, long lda, long
*ipiv, long *info);

Description

Oracle Solaris Studio Performance Library                          dsyconv(3P)



NAME
       dsyconv - convert A given by TRF into L and D and vice-versa


SYNOPSIS
       SUBROUTINE DSYCONV(UPLO, WAY, N, A, LDA, IPIV, WORK, INFO)


       CHARACTER*1 UPLO, WAY

       INTEGER INFO, LDA, N

       INTEGER IPIV(*)

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


       SUBROUTINE DSYCONV_64(UPLO, WAY, N, A, LDA, IPIV, WORK, INFO)


       CHARACTER*1 UPLO, WAY

       INTEGER*8 INFO, LDA, N

       INTEGER*8 IPIV(*)

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


   F95 INTERFACE
       SUBROUTINE SYCONV(UPLO, WAY, N, A, LDA, IPIV, WORK, INFO)


       INTEGER :: N, LDA, INFO

       CHARACTER(LEN=1) :: UPLO, WAY

       INTEGER, DIMENSION(:) :: IPIV

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

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


       SUBROUTINE SYCONV_64(UPLO, WAY, N, A, LDA, IPIV, WORK, INFO)


       INTEGER(8) :: N, LDA, INFO

       CHARACTER(LEN=1) :: UPLO, WAY

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

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

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


   C INTERFACE
       #include <sunperf.h>

       void  dsyconv  (char  uplo,  char  way,  int n, double *a, int lda, int
                 *ipiv, int *info);


       void dsyconv_64 (char uplo, char way, long n, double *a, long lda, long
                 *ipiv, long *info);


PURPOSE
       dsyconv  convert  A given by TRF into L and D and vice-versa.  Get Non-
       diag elements of D (returned in workspace) and apply or reverse  permu-
       tation done in TRF.


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.


       WAY (input)
                 WAY is CHARACTER*1
                 = 'C': Convert
                 = 'R': Revert


       N (input)
                 N is INTEGER
                 The order of the matrix A.  N >= 0.


       A (input/output)
                 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.


       WORK (output)
                 WORK is DOUBLE PRECISION 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                       dsyconv(3P)