Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

sgbtf2 (3p)

Name

sgbtf2 - n band matrix A using partial pivoting with row interchanges

Synopsis

SUBROUTINE SGBTF2(M, N, KL, KU, AB, LDAB, IPIV, INFO)

INTEGER M, N, KL, KU, LDAB, INFO
INTEGER IPIV(*)
REAL AB(LDAB,*)

SUBROUTINE SGBTF2_64(M, N, KL, KU, AB, LDAB, IPIV, INFO)

INTEGER*8 M, N, KL, KU, LDAB, INFO
INTEGER*8 IPIV(*)
REAL AB(LDAB,*)




F95 INTERFACE
SUBROUTINE GBTF2(M, N, KL, KU, AB, LDAB, IPIV, INFO)

INTEGER :: M, N, KL, KU, LDAB, INFO
INTEGER, DIMENSION(:) :: IPIV
REAL, DIMENSION(:,:) :: AB

SUBROUTINE GBTF2_64(M, N, KL, KU, AB, LDAB, IPIV, INFO)

INTEGER(8) :: M, N, KL, KU, LDAB, INFO
INTEGER(8), DIMENSION(:) :: IPIV
REAL, DIMENSION(:,:) :: AB




C INTERFACE
#include <sunperf.h>

void sgbtf2(int m, int n, int kl, int ku,  float  *ab,  int  ldab,  int
*ipiv, int *info);

void  sgbtf2_64(long m, long n, long kl, long ku, float *ab, long ldab,
long *ipiv, long *info);

Description

Oracle Solaris Studio Performance Library                           sgbtf2(3P)



NAME
       sgbtf2  -  compute  an  LU factorization of a real m-by-n band matrix A
       using partial pivoting with row interchanges


SYNOPSIS
       SUBROUTINE SGBTF2(M, N, KL, KU, AB, LDAB, IPIV, INFO)

       INTEGER M, N, KL, KU, LDAB, INFO
       INTEGER IPIV(*)
       REAL AB(LDAB,*)

       SUBROUTINE SGBTF2_64(M, N, KL, KU, AB, LDAB, IPIV, INFO)

       INTEGER*8 M, N, KL, KU, LDAB, INFO
       INTEGER*8 IPIV(*)
       REAL AB(LDAB,*)




   F95 INTERFACE
       SUBROUTINE GBTF2(M, N, KL, KU, AB, LDAB, IPIV, INFO)

       INTEGER :: M, N, KL, KU, LDAB, INFO
       INTEGER, DIMENSION(:) :: IPIV
       REAL, DIMENSION(:,:) :: AB

       SUBROUTINE GBTF2_64(M, N, KL, KU, AB, LDAB, IPIV, INFO)

       INTEGER(8) :: M, N, KL, KU, LDAB, INFO
       INTEGER(8), DIMENSION(:) :: IPIV
       REAL, DIMENSION(:,:) :: AB




   C INTERFACE
       #include <sunperf.h>

       void sgbtf2(int m, int n, int kl, int ku,  float  *ab,  int  ldab,  int
                 *ipiv, int *info);

       void  sgbtf2_64(long m, long n, long kl, long ku, float *ab, long ldab,
                 long *ipiv, long *info);



PURPOSE
       sgbtf2 computes an LU factorization of a  real  m-by-n  band  matrix  A
       using partial pivoting with row interchanges.

       This is the unblocked version of the algorithm, calling Level 2 BLAS.


ARGUMENTS
       M (input) The number of rows of the matrix A. M >= 0.


       N (input) The number of columns 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.


       AB (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 AB as follows:
                 AB(kl+ku+1+i-j,j)=A(i,j) for max(1,j-ku)<=i<=min(m,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.


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


       IPIV (output)
                 The  pivot  indices;  for  1  <=  i <= min(M,N), row i of the
                 matrix was interchanged with row IPIV(i).


       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
                 division by zero will occur if it is used to solve  a  system
                 of equations.


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                        sgbtf2(3P)