Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

sgbsv (3p)

Name

sgbsv - compute the solution to a real system of linear equations A*X=B, where A is a band matrix of order N with KL subdiagonals and KU superdiagonals, and X and B are N-by-NRHS matrices

Synopsis

SUBROUTINE SGBSV(N, KL, KU, NRHS, A, LDA, IPIVOT, B, LDB, INFO)

INTEGER N, KL, KU, NRHS, LDA, LDB, INFO
INTEGER IPIVOT(*)
REAL A(LDA,*), B(LDB,*)

SUBROUTINE SGBSV_64(N, KL, KU, NRHS, A, LDA, IPIVOT, B, LDB,
INFO)

INTEGER*8 N, KL, KU, NRHS, LDA, LDB, INFO
INTEGER*8 IPIVOT(*)
REAL A(LDA,*), B(LDB,*)




F95 INTERFACE
SUBROUTINE GBSV(N, KL, KU, NRHS, A, LDA, IPIVOT, B, LDB,
INFO)

INTEGER :: N, KL, KU, NRHS, LDA, LDB, INFO
INTEGER, DIMENSION(:) :: IPIVOT
REAL, DIMENSION(:,:) :: A, B

SUBROUTINE GBSV_64(N, KL, KU, NRHS, A, LDA, IPIVOT, B,
LDB, INFO)

INTEGER(8) :: N, KL, KU, NRHS, LDA, LDB, INFO
INTEGER(8), DIMENSION(:) :: IPIVOT
REAL, DIMENSION(:,:) :: A, B




C INTERFACE
#include <sunperf.h>

void  sgbsv(int  n,  int  kl,  int ku, int nrhs, float *a, int lda, int
*ipivot, float *b, int ldb, int *info);

void sgbsv_64(long n, long kl, long ku, long nrhs, float *a, long  lda,
long *ipivot, float *b, long ldb, long *info);

Description

Oracle Solaris Studio Performance Library                            sgbsv(3P)



NAME
       sgbsv  -  compute  the  solution  to  a real system of linear equations
       A*X=B, where A is a band matrix of order N with KL subdiagonals and  KU
       superdiagonals, and X and B are N-by-NRHS matrices


SYNOPSIS
       SUBROUTINE SGBSV(N, KL, KU, NRHS, A, LDA, IPIVOT, B, LDB, INFO)

       INTEGER N, KL, KU, NRHS, LDA, LDB, INFO
       INTEGER IPIVOT(*)
       REAL A(LDA,*), B(LDB,*)

       SUBROUTINE SGBSV_64(N, KL, KU, NRHS, A, LDA, IPIVOT, B, LDB,
             INFO)

       INTEGER*8 N, KL, KU, NRHS, LDA, LDB, INFO
       INTEGER*8 IPIVOT(*)
       REAL A(LDA,*), B(LDB,*)




   F95 INTERFACE
       SUBROUTINE GBSV(N, KL, KU, NRHS, A, LDA, IPIVOT, B, LDB,
              INFO)

       INTEGER :: N, KL, KU, NRHS, LDA, LDB, INFO
       INTEGER, DIMENSION(:) :: IPIVOT
       REAL, DIMENSION(:,:) :: A, B

       SUBROUTINE GBSV_64(N, KL, KU, NRHS, A, LDA, IPIVOT, B,
              LDB, INFO)

       INTEGER(8) :: N, KL, KU, NRHS, LDA, LDB, INFO
       INTEGER(8), DIMENSION(:) :: IPIVOT
       REAL, DIMENSION(:,:) :: A, B




   C INTERFACE
       #include <sunperf.h>

       void  sgbsv(int  n,  int  kl,  int ku, int nrhs, float *a, int lda, int
                 *ipivot, float *b, int ldb, int *info);

       void sgbsv_64(long n, long kl, long ku, long nrhs, float *a, long  lda,
                 long *ipivot, float *b, long ldb, long *info);



PURPOSE
       sgbsv computes the solution to a real system of linear equations A*X=B,
       where A is a band matrix of order N with KL subdiagonals and KU  super-
       diagonals, and X and B are N-by-NRHS matrices.

       The LU decomposition with partial pivoting and row interchanges is used
       to factor A as A=L*U, where L is a  product  of  permutation  and  unit
       lower triangular matrices with KL subdiagonals, and U is upper triangu-
       lar with KL+KU superdiagonals. The factored form of A is then  used  to
       solve the system of equations A*X=B.


ARGUMENTS
       N (input) The number of linear equations, i.e., the order of the matrix
                 A. N >= 0.


       KL (input)
                 The number of subdiagonals within the band of A. KL >= 0.


       KU (input)
                 The number of superdiagonals within the band of A. KU >= 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  matrix  A  in  band storage, in rows KL+1 to
                 2*KL+KU+1; rows 1 to KL of the array need not be set.
                 The j-th column of A is stored in  the  j-th  column  of  the
                 array A as follows:
                 A(KL+KU+1+i-j,j)=A(i,j) for max(1,j-KU)<=i<=min(N,j+KL)

                 On  exit,  details  of  the  factorization: U is stored as an
                 upper triangular band matrix  with  KL+KU  superdiagonals  in
                 rows  1  to KL+KU+1, and the multipliers used during the fac-
                 torization are stored in  rows  KL+KU+2  to  2*KL+KU+1.   See
                 below for further details.


       LDA (input)
                 The leading dimension of the array A. LDA >= 2*KL+KU+1.


       IPIVOT (output)
                 The pivot indices that define the permutation matrix P; row i
                 of the matrix was interchanged with row IPIVOT(i).


       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, U(i,i) is exactly zero.  The factorization
                 has been completed, but the factor U is exactly singular, and
                 the solution has not been computed.


FURTHER DETAILS
       The band storage scheme is illustrated by the following example, when M
       = N = 6, KL = 2, KU = 1:

       On entry:                       On exit:

        *   *   *   +   +   +      *   *   *  u14 u25 u36
        *   *   +   +   +   +      *   *  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
       a21 a32 a43 a54 a65  *     m21 m32 m43 m54 m65  *
       a31 a42 a53 a64  *   *     m31 m42 m53 m64  *   *

       Array elements marked * are not used by the routine; elements marked  +
       need not be set on entry, but are required by the routine to store ele-
       ments of U because of fill-in resulting from the row interchanges.




                                  7 Nov 2015                         sgbsv(3P)