Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cpbsv (3p)

Name

cpbsv - compute the solution to a complex system of linear equations A*X=B, where A is an N-by-N Hermitian positive definite band matrix and X and B are N-by-NRHS matrices

Synopsis

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

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

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

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




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

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

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

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




C INTERFACE
#include <sunperf.h>

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

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

Description

Oracle Solaris Studio Performance Library                            cpbsv(3P)



NAME
       cpbsv  -  compute  the solution to a complex system of linear equations
       A*X=B, where A is an N-by-N Hermitian positive definite band matrix and
       X and B are N-by-NRHS matrices


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

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

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

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




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

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

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

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




   C INTERFACE
       #include <sunperf.h>

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

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



PURPOSE
       cpbsv  computes  the  solution  to a complex system of linear equations
       A*X=B, where A is an N-by-N Hermitian positive definite band matrix and
       X and B are N-by-NRHS matrices.

       The Cholesky decomposition is used to factor A as
          A = U**H * U,  if UPLO = 'U', or
          A = L * L**H,  if UPLO = 'L',
       where U is an upper triangular band matrix, and L is a lower triangular
       band matrix, with the same number of superdiagonals or subdiagonals  as
       A. The factored form of A is then used to solve the system of equations
       A*X=B.


ARGUMENTS
       UPLO (input)
                 = 'U':  Upper triangle of A is stored;
                 = 'L':  Lower triangle of A is stored.


       N (input) The number of linear equations, i.e., 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/output)
                 On  entry,  the upper or lower triangle of the Hermitian band
                 matrix A, stored in the first KD+1 rows of the array.
                 The j-th column of A is stored in  the  j-th  column  of  the
                 array A as follows:
                 if UPLO='U', A(KD+1+i-j,j)=A(i,j) for max(1,j-KD)<=i<=j;
                 if UPLO='L', A(1+i-j,j)=A(i,j) for j<=i<=min(N,j+KD).
                 See below for further details.

                 On  exit,  if INFO = 0, the triangular factor U or L from the
                 Cholesky factorization A = U**H*U or A = L*L**H of  the  band
                 matrix A, in the same storage format as A.


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


       B (input/output)
                 On entry, the N-by-NRHS right hand side matrix B.
                 On exit, if INFO = 0, the N-by-NRHS solution 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;
                 >  0:   if INFO = i, the leading minor of order i of A is not
                 positive definite, so the factorization  could  not  be  com-
                 pleted, and the solution has not been computed.


FURTHER DETAILS
       The band storage scheme is illustrated by the following example, when N
       = 6, KD = 2, and UPLO = 'U':

       On entry:                       On exit:

        *   *  a13 a24 a35 a46     *   *  u13 u24 u35 u46
        *  a12 a23 a34 a45 a56     *  u12 u23 u34 u45 u56
       a11 a22 a33 a44 a55 a66    u11 u22 u33 u44 u55 u66

       Similarly, if UPLO = 'L' the format of A is as follows:

       On entry:                       On exit:

       a11 a22 a33 a44 a55 a66    l11 l22 l33 l44 l55 l66
       a21 a32 a43 a54 a65  *     l21 l32 l43 l54 l65  *
       a31 a42 a53 a64  *   *     l31 l42 l53 l64  *   *

       Array elements marked * are not used by the routine.




                                  7 Nov 2015                         cpbsv(3P)