Previous Next Contents Generated Index Doc Set Home



Cholesky Factorization and Condition Number of a Symmetric Positive Definite Matrix

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

Calling Sequence

CALL DPOCO 
(DA, LDA, N, DRCOND, DWORK, INFO)
CALL SPOCO 
(SA, LDA, N, SRCOND, SWORK, INFO)
CALL ZPOCO 
(ZA, LDA, N, DRCOND, ZWORK, INFO)
CALL CPOCO 
(CA, LDA, N, SRCOND, CWORK, INFO)






void dpoco 
(double *da, int lda, int n, double *drcond, int *info)
void spoco 
(float *sa, int lda, int n, float *srcond, int *info)
void zpoco 
(doublecomplex *za, int lda, int n, double *drcond, int 
*info)
void cpoco 
(complex *ca, int lda, int n, float *srcond, 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.

xRCOND

On exit, an estimate of the reciprocal condition number of A.
0.0 RCOND 1.0. As the value of RCOND gets smaller, operations with A such as solving Ax = b may become less stable. If RCOND satisfies RCOND + 1.0 = 1.0 then A may be singular to working precision.

xWORK

Scratch array with a dimension of N.

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 = 4)
      PARAMETER        (LDA = N)
C
      DOUBLE PRECISION  A(LDA,N), B(N), RCOND, WORK(N)
      INTEGER           ICOL, INFO, IROW
C
      EXTERNAL          DPOCO, 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          2  -1   0   0        40
C     A = -1   2  -1   0    b = 30
C          0  -1   2  -1        20
C          0   0  -1   2        10
C
      DATA A / 2.0D0, 3*8D8, -1.0D0, 2.0D0, 2*8D8, 0.0D0, -1.0D0,
     $         2.0D0, -1.0D0, 0.0D0, 0.0D0, -1.0D0, 2.0D0 /
      DATA B / 4.0D0, 3.0D0, 2.0D0, 1.0D0 /
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 DPOCO (A, LDA, N, RCOND, WORK, INFO)
      IF (INFO .EQ. 0) THEN
        IF ((RCOND + 1.0D0) .EQ. 1.0D0) THEN
          PRINT 1070
        END IF
        CALL DPOSL (A, LDA, N, B)
        PRINT 1050
        PRINT 1040, B
        PRINT 1060, RCOND
      ELSE
        PRINT 1080
      END IF
C
 1000 FORMAT (1X, 'A in full form:')
 1010 FORMAT (4(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, 'Reciprocal condition number of A:', F5.1)
 1070 FORMAT (1X, 'A may be singular to working precision.')
 1080 FORMAT (1X, 'A is not positive definite.')
C
      END
 

Sample Output

 
 A in full form:
     2.000    -1.000     0.000     0.000
    -1.000     2.000    -1.000     0.000
     0.000    -1.000     2.000    -1.000
     0.000     0.000    -1.000     2.000



 A in symmetric form:  (* in unused entries)
     2.000    -1.000     0.000     0.000
   *******     2.000    -1.000     0.000
   *******   *******     2.000    -1.000
   *******   *******    -1.000     2.000



 b:
     4.000
     3.000
     2.000
     1.000



 A**(-1) * b:
     6.000
     8.000
     7.000
     4.000



 Reciprocal condition number of A:  0.1






Previous Next Contents Generated Index Doc Set Home