Previous Next Contents Generated Index Doc Set Home



Cholesky Factorization of a Symmetric Positive Definite Matrix

The subroutines described in this section compute a Cholesky factorization of a symmetric positive definite matrix A. It is typical to follow a call to xPOFA with a call to xPOSL to solve Ax = b or to xPODI to compute the determinant and inverse of A.

Calling Sequence

CALL DPOFA 
(DA, LDA, N, INFO)
CALL SPOFA 
(SA, LDA, N, INFO)
CALL ZPOFA 
(ZA, LDA, N, INFO)
CALL CPOFA 
(CA, LDA, N, INFO)






void dpofa 
(double *da, int lda, int n, int *info)
void spofa 
(float *sa, int lda, int n, int *info)
void zpofa 
(doublecomplex *za, int lda, int n, int *info)
void cpofa 
(complex *ca, int lda, int n, int *info)

Arguments

xA

On entry, the upper triangle of the matrix A.
On exit, a Cholesky factorization of the matrix A. The strict lower triangle of A is not referenced.

LDA

Leading dimension of the array A as specified in a dimension or type statement. LDA max(1,N).

N

Order of the matrix A. N 0.

INFO

On exit:

INFO = 0

Subroutine completed normally.

INFO > 0

Returns a value k if the leading minor of order k is not positive definite.

Sample Program

 
      PROGRAM TEST
      IMPLICIT NONE
C
      INTEGER           LDA, N
      PARAMETER        (N = 5)
      PARAMETER        (LDA = N)
C
      DOUBLE PRECISION  A(LDA,N), B(N)
      INTEGER           ICOL, INFO, IROW
C
      EXTERNAL          DPOFA, DPOSL
C
C     Initialize the array A to store in symmetric storage mode
C     the matrix A shown below.  Initialize the array B to store
C     the vector B shown below.
C
C          5  4  3  2  1        120
C          4  5  4  3  2         60
C     A =  3  4  5  4  3    b =  40
C          2  3  4  5  4         60
C          1  2  3  4  5        120
C
      DATA A / 5.0D0, 4*8D8, 4.0D0, 5.0D0, 3*8D8, 3.0D0, 4.0D0,
     $         5.0D0, 2*8D8, 2.0D0, 3.0D0, 4.0D0, 5.0D0, 1*8D8,
     $         1.0D0, 2.0D0, 3.0D0, 4.0D0, 5.0D0 /
      DATA B / 1.2D2, 6.0D1, 4.0D1, 6.0D1, 1.2D2 /
C
      PRINT 1000
      DO 100, IROW = 1, N
        PRINT 1010, (A(ICOL,IROW), ICOL = 1, IROW),
     $              (A(IROW,ICOL), ICOL = IROW + 1, N)
  100 CONTINUE
      PRINT 1020
      PRINT 1010, ((A(IROW,ICOL), ICOL = 1, N), IROW = 1, N)
      PRINT 1030
      PRINT 1040, B
      CALL DPOFA (A, LDA, N, INFO)
      IF (INFO .EQ. 0) THEN
        CALL DPOSL (A, LDA, N, B)
        PRINT 1050
        PRINT 1040, B
      ELSE
        PRINT 1060
      END IF
C
 1000 FORMAT (1X, 'A in full form:')
 1010 FORMAT (5(3X, F7.3))
 1020 FORMAT (/1X, 'A in symmetric form:  (* in unused entries)')
 1030 FORMAT (/1X, 'b:')
 1040 FORMAT (3X, F7.3)
 1050 FORMAT (/1X, 'A**(-1) * b:')
 1060 FORMAT (/1X, 'A is not positive definite.')
C
      END
 

Sample Output

 
 A in full form:
     5.000     4.000     3.000     2.000     1.000
     4.000     5.000     4.000     3.000     2.000
     3.000     4.000     5.000     4.000     3.000
     2.000     3.000     4.000     5.000     4.000
     1.000     2.000     3.000     4.000     5.000



 A in symmetric form:  (* in unused entries)
     5.000     4.000     3.000     2.000     1.000
   *******     5.000     4.000     3.000     2.000
   *******   *******     5.000     4.000     3.000
   *******   *******   *******     5.000     4.000
   *******   *******   *******   *******     5.000



 b:
   120.000
    60.000
    40.000
    60.000
   120.000



 A**(-1) * b:
    50.000
   -20.000
   -20.000
   -20.000
    50.000






Previous Next Contents Generated Index Doc Set Home