Previous Next Contents Generated Index Doc Set Home



Update an Augmented Cholesky Decomposition with Permutations

The subroutines described in this section compute the Cholesky decomposition of a symmetric positive definite matrix A.

Calling Sequence

CALL DCHEX 
(DA, LDA, N, K, L, DZ, LDZ, NZ, DCOS, DSIN, JOB)
CALL SCHEX 
(SA, LDA, N, K, L, SZ, LDZ, NZ, SCOS, SSIN, JOB)
CALL CCHEX 
(ZA, LDA, N, K, L, ZZ, LDZ, NZ, DCOS, ZSIN, JOB)
CALL ZCHEX 
(CA, LDA, N, K, L, CZ, LDZ, NZ, SCOS, CSIN, JOB)






void dchex 
(double *da, int lda, int n, int k, int l, double *dz, 
int ldz, int nz, double *dcos, double *dsin, int job)
void schex 
(float *da, int lda, int n, int k, int l, float *sz, 
int ldz, int nz, float *scos, float *ssin, int job)
void zchex 
(doublecomplex *za, int lda, int n, int k, int l, 
doublecomplex *zz, int ldz, int nz, double *dcos, 
doublecomplex *zsin, int job)
void cchex 
(complex*r, int lda, int n, int k, int l, complex *cz, 
int ldz, int nz, float *scos, complex *csin, int job)

Arguments

xA

On entry, the upper triangle of the matrix A.
On exit, the upper triangle of A contains the upper triangle of the updated factor. 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.

K

First column to be permuted. 1 K < L.

L

Last column to be permuted; must be strictly greater than K.
K < L N.

xZ

Array of vectors into which the transformation U is multiplied. Not used if NZ = 0.

LDZ

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

NZ

Number of columns in the matrix Z. NZ 0.

xCOS

Cosines of the transforming rotations.

xSIN

Sines of the transforming rotations.

JOB

Determines the type of permutation:

1

right circular shift

2

left circular shift

Sample Program

 
      PROGRAM TEST
      IMPLICIT NONE
C
      INTEGER           ISHFRT, LDA, N, NULL, NZ
      PARAMETER        (ISHFRT = 1)
      PARAMETER        (N = 4)
      PARAMETER        (LDA = N)
      PARAMETER        (NULL = 1)
      PARAMETER        (NZ = 0)
C
      DOUBLE PRECISION  A(LDA,N), ANULL, C(N), S(N), WORK(N)
      INTEGER           ICOL, INFO, IPIVOT(N), IROW, JOB, K
C
      EXTERNAL          DCHDC, DCHEX
C
C     Initialize the arrays A and Z to store the matrices A and Z
C     shown below and initialize X and Y to store the vectors x
C     and y shown below.
C
C         4  3  2  1        1
C     A = 3  4  3  2    x = 1
C         2  3  4  3        1
C         1  2  3  4        1
C
      DATA A / 4.0D0, 3*8D8, 3.0D0, 4.0D0, 2*8D8, 2.0D0, 3.0D0,
     $         4.0D0, 8D8, 1.0D0, 2.0D0, 3.0D0, 4.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)
      CALL DCHDC (A, LDA, N, WORK, IPIVOT, JOB, INFO)
      IF (INFO .EQ. N) THEN
        PRINT 1030
        PRINT 1010, A(1,1), A(1,2), A(1,3), A(1,4)
        PRINT 1040,         A(2,2), A(2,3), A(2,4)
        PRINT 1050,                 A(3,3), A(3,4)
        PRINT 1060,                         A(4,4)
        K = 1
        ANULL = 0.0D0
        JOB = ISHFRT
        CALL DCHEX (A, LDA, N, K, N, ANULL, NULL, NZ, C, S, JOB)
        PRINT 1070
        PRINT 1010, A(1,1), A(1,2), A(1,3), A(1,4)
        PRINT 1040,         A(2,2), A(2,3), A(2,4)
        PRINT 1050,                 A(3,3), A(3,4)
        PRINT 1060,                         A(4,4)
        PRINT 1080
        PRINT 1090, (C(IROW), S(IROW), IROW = 1, N)
      ELSE
        PRINT 1100
      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, 'Upper Cholesky factor:')
 1040 FORMAT (10X, 3(3X, F7.3))
 1050 FORMAT (20X, 2(3X, F7.3))
 1060 FORMAT (30X, 1(3X, F7.3))
 1070 FORMAT (1X, 'Updated Cholesky factor:')
 1080 FORMAT (/1X, 'Cosine', 3X, '  Sine')
 1090 FORMAT (1X, F6.3, 3X, F6.3)
 1100 FORMAT (/1X, 'A is not positive definite.')
C
      END
 

Sample Output

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



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



 Upper Cholesky factor:
     2.000     1.500     1.000     0.500
               1.323     1.134     0.945
                         1.309     1.091
                                   1.291
 Updated Cholesky factor:
     2.000     0.500     1.000     1.500
              -1.936    -1.291    -0.645
                        -1.155    -0.577
                                  -1.000



 Cosine     Sine
  0.645    0.764
  0.488    0.873
  0.250    0.968
  0.000    2.000






Previous Next Contents Generated Index Doc Set Home