Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dtpttr (3p)

Name

dtpttr - copy a triangular matrix from the standard packed format (TP) to the standard full format (TR)

Synopsis

SUBROUTINE DTPTTR(UPLO, N, AP, A, LDA, INFO)


CHARACTER*1 UPLO

INTEGER INFO, N, LDA

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


SUBROUTINE DTPTTR_64(UPLO, N, AP, A, LDA, INFO)


CHARACTER*1 UPLO

INTEGER*8 INFO, N, LDA

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


F95 INTERFACE
SUBROUTINE TPTTR(UPLO, N, AP, A, LDA, INFO)


INTEGER :: N, LDA, INFO

CHARACTER(LEN=1) :: UPLO

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

REAL(8), DIMENSION(:) :: AP


SUBROUTINE TPTTR_64(UPLO, N, AP, A, LDA, INFO)


INTEGER(8) :: N, LDA, INFO

CHARACTER(LEN=1) :: UPLO

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

REAL(8), DIMENSION(:) :: AP


C INTERFACE
#include <sunperf.h>

void dtpttr (char uplo, int n, double *ap,  double  *a,  int  lda,  int
*info);


void  dtpttr_64  (char  uplo,  long n, double *ap, double *a, long lda,
long *info);

Description

Oracle Solaris Studio Performance Library                           dtpttr(3P)



NAME
       dtpttr  - copy a triangular matrix from the standard packed format (TP)
       to the standard full format (TR)


SYNOPSIS
       SUBROUTINE DTPTTR(UPLO, N, AP, A, LDA, INFO)


       CHARACTER*1 UPLO

       INTEGER INFO, N, LDA

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


       SUBROUTINE DTPTTR_64(UPLO, N, AP, A, LDA, INFO)


       CHARACTER*1 UPLO

       INTEGER*8 INFO, N, LDA

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


   F95 INTERFACE
       SUBROUTINE TPTTR(UPLO, N, AP, A, LDA, INFO)


       INTEGER :: N, LDA, INFO

       CHARACTER(LEN=1) :: UPLO

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

       REAL(8), DIMENSION(:) :: AP


       SUBROUTINE TPTTR_64(UPLO, N, AP, A, LDA, INFO)


       INTEGER(8) :: N, LDA, INFO

       CHARACTER(LEN=1) :: UPLO

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

       REAL(8), DIMENSION(:) :: AP


   C INTERFACE
       #include <sunperf.h>

       void dtpttr (char uplo, int n, double *ap,  double  *a,  int  lda,  int
                 *info);


       void  dtpttr_64  (char  uplo,  long n, double *ap, double *a, long lda,
                 long *info);


PURPOSE
       dtpttr copies a triangular matrix A from standard packed format (TP) to
       standard full format (TR).


ARGUMENTS
       UPLO (input)
                 UPLO is CHARACTER*1
                 = 'U':  A is upper triangular.
                 = 'L':  A is lower triangular.


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


       AP (input)
                 AP is DOUBLE PRECISION array, dimension ( N*(N+1)/2 ),
                 On  entry,  the  upper  or  lower triangular matrix A, packed
                 columnwise in a linear array. The j-th column of A is  stored
                 in the array AP as follows:
                 if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
                 if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.


       A (output)
                 A is DOUBLE PRECISION array, dimension ( LDA, N )
                 On  exit, the triangular matrix A. If UPLO = 'U', the leading
                 N-by-N upper triangular part of A contains the upper triangu-
                 lar  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.


       LDA (input)
                 LDA is INTEGER
                 The leading dimension of the array A.
                 LDA >= 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                        dtpttr(3P)