Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dpbtrs (3p)

Name

dpbtrs - solve a system of linear equations A*X = B with a symmetric positive definite band matrix A using the Cholesky factorization A = U**T*U or A = L*L**T computed by DPBTRF

Synopsis

SUBROUTINE DPBTRS(UPLO, N, KD, NRHS, A, LDA, B, LDB, INFO)

CHARACTER*1 UPLO
INTEGER N, KD, NRHS, LDA, LDB, INFO
DOUBLE PRECISION A(LDA,*), B(LDB,*)

SUBROUTINE DPBTRS_64(UPLO, N, KD, NRHS, A, LDA, B, LDB, INFO)

CHARACTER*1 UPLO
INTEGER*8 N, KD, NRHS, LDA, LDB, INFO
DOUBLE PRECISION A(LDA,*), B(LDB,*)




F95 INTERFACE
SUBROUTINE PBTRS(UPLO, N, KD, NRHS, A, LDA, B, LDB, INFO)

CHARACTER(LEN=1) :: UPLO
INTEGER :: N, KD, NRHS, LDA, LDB, INFO
REAL(8), DIMENSION(:,:) :: A, B

SUBROUTINE PBTRS_64(UPLO, N, KD, NRHS, A, LDA, B, LDB,
INFO)

CHARACTER(LEN=1) :: UPLO
INTEGER(8) :: N, KD, NRHS, LDA, LDB, INFO
REAL(8), DIMENSION(:,:) :: A, B




C INTERFACE
#include <sunperf.h>

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

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

Description

Oracle Solaris Studio Performance Library                           dpbtrs(3P)



NAME
       dpbtrs  -  solve  a system of linear equations A*X = B with a symmetric
       positive definite band matrix A using the Cholesky  factorization  A  =
       U**T*U or A = L*L**T computed by DPBTRF


SYNOPSIS
       SUBROUTINE DPBTRS(UPLO, N, KD, NRHS, A, LDA, B, LDB, INFO)

       CHARACTER*1 UPLO
       INTEGER N, KD, NRHS, LDA, LDB, INFO
       DOUBLE PRECISION A(LDA,*), B(LDB,*)

       SUBROUTINE DPBTRS_64(UPLO, N, KD, NRHS, A, LDA, B, LDB, INFO)

       CHARACTER*1 UPLO
       INTEGER*8 N, KD, NRHS, LDA, LDB, INFO
       DOUBLE PRECISION A(LDA,*), B(LDB,*)




   F95 INTERFACE
       SUBROUTINE PBTRS(UPLO, N, KD, NRHS, A, LDA, B, LDB, INFO)

       CHARACTER(LEN=1) :: UPLO
       INTEGER :: N, KD, NRHS, LDA, LDB, INFO
       REAL(8), DIMENSION(:,:) :: A, B

       SUBROUTINE PBTRS_64(UPLO, N, KD, NRHS, A, LDA, B, LDB,
              INFO)

       CHARACTER(LEN=1) :: UPLO
       INTEGER(8) :: N, KD, NRHS, LDA, LDB, INFO
       REAL(8), DIMENSION(:,:) :: A, B




   C INTERFACE
       #include <sunperf.h>

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

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



PURPOSE
       dpbtrs  solves  a  system  of linear equations A*X = B with a symmetric
       positive definite band matrix A using the Cholesky  factorization  A  =
       U**T*U or A = L*L**T computed by DPBTRF.


ARGUMENTS
       UPLO (input)
                 = 'U':  Upper triangular factor stored in A;
                 = 'L':  Lower triangular factor stored in A.


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


       KD (input)
                 The  number  of superdiagonals of the matrix A if UPLO = 'U',
                 or the number of subdiagonals if UPLO = 'L'.  KD >= 0.


       NRHS (input)
                 The number of right hand sides, i.e., the number  of  columns
                 of the matrix B.  NRHS >= 0.


       A (input) The  triangular factor U or L from the Cholesky factorization
                 A = U**T*U or A = L*L**T of the band matrix A, stored in  the
                 first  KD+1  rows of the array.  The j-th column of U or L is
                 stored in the j-th column of the array A as follows: if  UPLO
                 ='U',  A(kd+1+i-j,j)  = U(i,j) for max(1,j-kd)<=i<=j; if UPLO
                 ='L', A(1+i-j,j)    = L(i,j) for j<=i<=min(n,j+kd).


       LDA (input)
                 The leading dimension of the array A.  LDA >= KD+1.


       B (input/output)
                 On entry, the right hand side matrix B.  On exit,  the  solu-
                 tion matrix X.


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


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




                                  7 Nov 2015                        dpbtrs(3P)