Previous Next Contents Generated Index Doc Set Home



LU Factorization of a General Matrix in Banded Storage

The subroutines described in this section compute the LU factorization of a matrix A in banded storage. It is typical to follow a call to xGBFA with a call to xGBSL to solve Ax = b or to xGBDI to compute the determinant of A.

Calling Sequence

CALL DGBFA 
(DA, LDA, N, NSUB, NSUPER, IPIVOT, INFO)
CALL SGBFA 
(SA, LDA, N, NSUB, NSUPER, IPIVOT, INFO)
CALL ZGBFA 
(ZA, LDA, N, NSUB, NSUPER, IPIVOT, INFO)
CALL CGBFA 
(CA, LDA, N, NSUB, NSUPER, IPIVOT, INFO)






void dgbfa 
(double *da, int lda, int n, int nsub, int nsuper, int 
*ipivot, int *info)
void sgbfa 
(float *sa, int lda, int n, int nsub, int nsuper, int 
*ipivot, int *info)
void zgbfa 
(doublecomplex *za, int lda, int n, int nsub, int 
nsuper, int *ipivot, int *info)
void cgbfa 
(complex *ca, int lda, int n, int nsub, int nsuper, int 
*ipivot, int *info)

Arguments

xA

On entry, the matrix A.
On exit, an LU factorization of the matrix A.

LDA

Leading dimension of the array A as specified in a dimension or type statement. LDA 2 × NSUB + NSUPER + 1.

N

Order of the matrix A. N 0.

NSUB

Number of subdiagonals of A. N-1 NSUB 0 but if N = 0 then NSUB = 0.

NSUPER

Number of superdiagonals of A. N-1 NSUPER 0 but if N = 0 then NSUPER = 0.

IPIVOT

On exit, a vector of pivot indices.

INFO

On exit:

INFO = 0

Subroutine completed normally.

INFO > 0

Returns a value k if U(k,k) = 0 to indicate that xGESL will divide by zero if called.

Sample Program

 
      PROGRAM TEST
      IMPLICIT NONE
C
      INTEGER           IAXEQB, LDA, LDAB, N, NDIAG, NSUB, NSUPER
      PARAMETER        (IAXEQB = 0)
      PARAMETER        (N = 4)
      PARAMETER        (LDA = N)
      PARAMETER        (NSUB = 1)
      PARAMETER        (NSUPER = 1)
      PARAMETER        (NDIAG = NSUB + 1 + NSUPER)
      PARAMETER        (LDAB = 2 * NSUB + 1 + NSUPER)
C
      DOUBLE PRECISION  AB(LDAB,N), AG(LDA,N), B(N)
      INTEGER           ICOL, INFO, IPIVOT(N), IROW, IROWB, I1
      INTEGER           I2, JOB
C
      EXTERNAL          DGBFA, DGBSL
      INTRINSIC         MAX0, MIN0
C
C     Initialize the array AG to store the 4x4 matrix A with one
C     subdiagonal and one superdiagonal shown below.  Initialize
C     the array B to store the vector b shown below.
C
C           2  -1                5
C     AG = -1   2  -1        b = 5
C              -1   2  -1        5
C                  -1   2        5
C
      DATA AB / 16*8D8 /
      DATA AG /  2.0D0, -1.0D0,  2*0D0, -1.0D0,  2.0D0, -1.0D0,
     $           2*0D0, -1.0D0,  2.0D0, -1.0D0,  2*0D0, -1.0D0,
     $           2.0D0 /
      DATA B / N*5.0D0 /
C
C     Copy the matrix A from the array AG to the array AB.  The
C     matrix is stored in general storage mode in AG and it will
C     be stored in banded storage mode in AB.  The code to copy
C     from general to banded storage mode is taken from the
C     comment block in the original DGBFA by Cleve Moler.
C
      DO 10, ICOL = 1, N
        I1 = MAX0 (1, ICOL - NSUPER)
        I2 = MIN0 (N, ICOL + NSUB)
        DO 10, IROW = I1, I2
          IROWB = IROW - ICOL + NDIAG
          AB(IROWB,ICOL) = AG(IROW,ICOL)
   10   CONTINUE
   20 CONTINUE
C
C     Print the initial values of the arrays.
C
      PRINT 1000
      PRINT 1010, ((AG(IROW,ICOL), ICOL = 1, N), IROW = 1, N)
      PRINT 1020
      PRINT 1010, ((AB(IROW,ICOL), ICOL = 1, N),
     $             IROW = 2 * NSUB, 2 * NSUB + 1 + NSUPER)
      PRINT 1030
      PRINT 1040, B
C
C     Factor the matrix in banded form.
C
      CALL DGBFA (AB, LDA, N, NSUB, NSUPER, IPIVOT, INFO)
      IF (INFO .EQ. 0) THEN
        JOB = IAXEQB
        CALL DGBSL (AB, LDA, N, NSUB, NSUPER, IPIVOT, B, JOB)
        PRINT 1050
        PRINT 1040, B
      ELSE
        PRINT 1060
      END IF
C
 1000 FORMAT (1X, 'A in full form:')
 1010 FORMAT (4(3X, F4.1))
 1020 FORMAT (/1X, 'A in banded form:  (* in unused elements)')
 1030 FORMAT (/1X, 'b:')
 1040 FORMAT (3X, F4.1)
 1050 FORMAT (/1X, 'A**(-1) * b:')
 1060 FORMAT (1X, 'A is singular to working precision.')
C
      END
 

Sample Output

 
 A in full form:
    2.0   -1.0    0.0    0.0
   -1.0    2.0   -1.0    0.0
    0.0   -1.0    2.0   -1.0
    0.0    0.0   -1.0    2.0



 A in banded form:  (* in unused elements)
   ****   -1.0   -1.0   -1.0
    2.0    2.0    2.0    2.0
   -1.0   -1.0   -1.0   ****



 b:
    5.0
    5.0
    5.0
    5.0



 A**(-1) * b:
   10.0
   15.0
   15.0
   10.0






Previous Next Contents Generated Index Doc Set Home