MB02DD

Updating Cholesky factorization of a positive definite block Toeplitz matrix

[Specification] [Arguments] [Method] [References] [Comments] [Example]

Purpose

  To update the Cholesky factor and the generator and/or the
  Cholesky factor of the inverse of a symmetric positive definite
  (s.p.d.) block Toeplitz matrix T, given the information from
  a previous factorization and additional blocks in TA of its first
  block row, or its first block column, depending on the routine
  parameter TYPET. Transformation information is stored.

Specification
      SUBROUTINE MB02DD( JOB, TYPET, K, M, N, TA, LDTA, T, LDT, G,
     $                   LDG, R, LDR, L, LDL, CS, LCS, DWORK, LDWORK,
     $                   INFO )
C     .. Scalar Arguments ..
      CHARACTER         JOB, TYPET
      INTEGER           INFO, K, LCS, LDG, LDL, LDR, LDT, LDTA, LDWORK,
     $                  M, N
C     .. Array Arguments ..
      DOUBLE PRECISION  CS(*), DWORK(*), G(LDG, *), L(LDL,*), R(LDR,*),
     $                  T(LDT,*), TA(LDTA,*)

Arguments

Mode Parameters

  JOB     CHARACTER*1
          Specifies the output of the routine, as follows:
          = 'R':  updates the generator G of the inverse and
                  computes the new columns / rows for the Cholesky
                  factor R of T;
          = 'A':  updates the generator G, computes the new
                  columns / rows for the Cholesky factor R of T and
                  the new rows / columns for the Cholesky factor L
                  of the inverse;
          = 'O':  only computes the new columns / rows for the
                  Cholesky factor R of T.

  TYPET   CHARACTER*1
          Specifies the type of T, as follows:
          = 'R':  the first block row of an s.p.d. block Toeplitz
                  matrix was/is defined; if demanded, the Cholesky
                  factors R and L are upper and lower triangular,
                  respectively, and G contains the transposed
                  generator of the inverse;
          = 'C':  the first block column of an s.p.d. block Toeplitz
                  matrix was/is defined; if demanded, the Cholesky
                  factors R and L are lower and upper triangular,
                  respectively, and G contains the generator of the
                  inverse. This choice results in a column oriented
                  algorithm which is usually faster.
          Note:   in this routine, the notation x / y means that
                  x corresponds to TYPET = 'R' and y corresponds to
                  TYPET = 'C'.

Input/Output Parameters
  K       (input)  INTEGER
          The number of rows / columns in T, which should be equal
          to the blocksize.  K >= 0.

  M       (input)  INTEGER
          The number of blocks in TA.  M >= 0.

  N       (input)  INTEGER
          The number of blocks in T.  N >= 0.

  TA      (input/output)  DOUBLE PRECISION array, dimension
          (LDTA,M*K) / (LDTA,K)
          On entry, the leading K-by-M*K / M*K-by-K part of this
          array must contain the (N+1)-th to (N+M)-th blocks in the
          first block row / column of an s.p.d. block Toeplitz
          matrix.
          On exit, if INFO = 0, the leading K-by-M*K / M*K-by-K part
          of this array contains information on the Householder
          transformations used, such that the array

                     [ T  TA ]    /    [ T  ]
                                       [ TA ]

          serves as the new transformation matrix T for further
          applications of this routine.

  LDTA    INTEGER
          The leading dimension of the array TA.
          LDTA >= MAX(1,K),   if TYPET = 'R';
          LDTA >= MAX(1,M*K), if TYPET = 'C'.

  T       (input)  DOUBLE PRECISION array, dimension (LDT,N*K) /
          (LDT,K)
          The leading K-by-N*K / N*K-by-K part of this array must
          contain transformation information generated by the SLICOT
          Library routine MB02CD, i.e., in the first K-by-K block,
          the upper / lower Cholesky factor of T(1:K,1:K), and in
          the remaining part, the Householder transformations
          applied during the initial factorization process.

  LDT     INTEGER
          The leading dimension of the array T.
          LDT >= MAX(1,K),    if TYPET = 'R';
          LDT >= MAX(1,N*K),  if TYPET = 'C'.

  G       (input/output)  DOUBLE PRECISION array, dimension
          (LDG,( N + M )*K) / (LDG,2*K)
          On entry, if JOB = 'R', or 'A', then the leading
          2*K-by-N*K / N*K-by-2*K part of this array must contain,
          in the first K-by-K block of the second block row /
          column, the lower right block of the Cholesky factor of
          the inverse of T, and in the remaining part, the generator
          of the inverse of T.
          On exit, if INFO = 0 and JOB = 'R', or 'A', then the
          leading 2*K-by-( N + M )*K / ( N + M )*K-by-2*K part of
          this array contains the same information as on entry, now
          for the updated Toeplitz matrix. Actually, to obtain a
          generator of the inverse one has to set
            G(K+1:2*K, 1:K) = 0,    if TYPET = 'R';
            G(1:K, K+1:2*K) = 0,    if TYPET = 'C'.

  LDG     INTEGER
          The leading dimension of the array G.
          LDG >= MAX(1,2*K),  if TYPET = 'R' and JOB = 'R', or 'A';
          LDG >= MAX(1,( N + M )*K),
                              if TYPET = 'C' and JOB = 'R', or 'A';
          LDG >= 1,           if JOB = 'O'.

  R       (input/output)  DOUBLE PRECISION array, dimension
          (LDR,M*K) / (LDR,( N + M )*K)
          On input, the leading N*K-by-K part of R(K+1,1) /
          K-by-N*K part of R(1,K+1) contains the last block column /
          row of the previous Cholesky factor R.
          On exit, if INFO = 0, then the leading
          ( N + M )*K-by-M*K / M*K-by-( N + M )*K part of this
          array contains the last M*K columns / rows of the upper /
          lower Cholesky factor of T. The elements in the strictly
          lower / upper triangular part are not referenced.

  LDR     INTEGER
          The leading dimension of the array R.
          LDR >= MAX(1, ( N + M )*K), if TYPET = 'R';
          LDR >= MAX(1, M*K),         if TYPET = 'C'.

  L       (output)  DOUBLE PRECISION array, dimension
          (LDL,( N + M )*K) / (LDL,M*K)
          If INFO = 0 and JOB = 'A', then the leading
          M*K-by-( N + M )*K / ( N + M )*K-by-M*K part of this
          array contains the last M*K rows / columns of the lower /
          upper Cholesky factor of the inverse of T. The elements
          in the strictly upper / lower triangular part are not
          referenced.

  LDL     INTEGER
          The leading dimension of the array L.
          LDL >= MAX(1, M*K),         if TYPET = 'R' and JOB = 'A';
          LDL >= MAX(1, ( N + M )*K), if TYPET = 'C' and JOB = 'A';
          LDL >= 1,                   if JOB = 'R', or 'O'.

  CS      (input/output)  DOUBLE PRECISION array, dimension (LCS)
          On input, the leading 3*(N-1)*K part of this array must
          contain the necessary information about the hyperbolic
          rotations and Householder transformations applied
          previously by SLICOT Library routine MB02CD.
          On exit, if INFO = 0, then the leading 3*(N+M-1)*K part of
          this array contains information about all the hyperbolic
          rotations and Householder transformations applied during
          the whole process.

  LCS     INTEGER
          The length of the array CS.  LCS >= 3*(N+M-1)*K.

Workspace
  DWORK   DOUBLE PRECISION array, dimension (LDWORK)
          On exit, if INFO = 0,  DWORK(1)  returns the optimal
          value of LDWORK.
          On exit, if  INFO = -19,  DWORK(1)  returns the minimum
          value of LDWORK.

  LDWORK  INTEGER
          The length of the array DWORK.
          LDWORK >= MAX(1,(N+M-1)*K).
          For optimum performance LDWORK should be larger.

Error Indicator
  INFO    INTEGER
          = 0:  successful exit;
          < 0:  if INFO = -i, the i-th argument had an illegal
                value;
          = 1:  the reduction algorithm failed. The block Toeplitz
                matrix associated with [ T  TA ] / [ T'  TA' ]' is
                not (numerically) positive definite.

Method
  Householder transformations and modified hyperbolic rotations
  are used in the Schur algorithm [1], [2].

References
  [1] Kailath, T. and Sayed, A.
      Fast Reliable Algorithms for Matrices with Structure.
      SIAM Publications, Philadelphia, 1999.

  [2] Kressner, D. and Van Dooren, P.
      Factorizations and linear system solvers for matrices with
      Toeplitz structure.
      SLICOT Working Note 2000-2, 2000.

Numerical Aspects
  The implemented method is numerically stable.
                            3         2
  The algorithm requires 0(K ( N M + M ) ) floating point
  operations.

Further Comments
  For min(K,N,M) = 0, the routine sets DWORK(1) = 1 and returns.
  Although the calculations could still be performed when N = 0,
  but min(K,M) > 0, this case is not considered as an "update".
  SLICOT Library routine MB02CD should be called with the argument
  M instead of N.

Example

Program Text

*     MB02DD EXAMPLE PROGRAM TEXT
*     Copyright (c) 2002-2017 NICONET e.V.
*
*     .. Parameters ..
      INTEGER          NIN, NOUT
      PARAMETER        ( NIN = 5, NOUT = 6 )
      INTEGER          KMAX, MMAX, NMAX
      PARAMETER        ( KMAX = 20, MMAX = 20, NMAX = 20 )
      INTEGER          LCS, LDG, LDL, LDR, LDT, LDWORK
      PARAMETER        ( LDG = KMAX*( MMAX + NMAX ),
     $                   LDL = KMAX*( MMAX + NMAX ),
     $                   LDR = KMAX*( MMAX + NMAX ),
     $                   LDT = KMAX*( MMAX + NMAX ),
     $                   LDWORK = ( MMAX + NMAX - 1 )*KMAX )
      PARAMETER        ( LCS = 3*LDWORK )
*     .. Local Scalars ..
      INTEGER          I, INFO, J, K, M, N, S
      CHARACTER        JOB, TYPET
*     .. Local Arrays ..
*     The arrays are dimensioned for both TYPET = 'R' and TYPET = 'C'.
*     Arrays G and T could be smaller.
*     For array G, it is assumed that MMAX + NMAX >= 2.
*     The matrix TA is also stored in the array T.
      DOUBLE PRECISION CS(LCS), DWORK(LDWORK),
     $                 G(LDG, KMAX*( MMAX + NMAX )),
     $                 L(LDL, KMAX*( MMAX + NMAX )),
     $                 R(LDR, KMAX*( MMAX + NMAX )),
     $                 T(LDT, KMAX*( MMAX + NMAX ))
*     .. External Functions ..
      LOGICAL          LSAME
      EXTERNAL         LSAME
*     .. External Subroutines ..
      EXTERNAL         DLACPY, MB02CD, MB02DD
*
*     .. Executable Statements ..
      WRITE ( NOUT, FMT = 99999 )
*     Skip the heading in the data file and read the data.
      READ ( NIN, FMT = '()' )
      READ ( NIN, FMT = * ) N, K, M, JOB, TYPET
      S = ( N + M )*K
      IF ( N.LE.0 .OR. N.GT.NMAX ) THEN
         WRITE ( NOUT, FMT = 99989 ) N
      ELSE
         IF ( K.LE.0 .OR. K.GT.KMAX ) THEN
            WRITE ( NOUT, FMT = 99988 ) K
         ELSE
            IF ( M.LE.0 .OR. M.GT.MMAX ) THEN
               WRITE ( NOUT, FMT = 99987 ) M
            ELSE
               IF ( LSAME( TYPET, 'R' ) ) THEN
                  READ ( NIN, FMT = * ) ( ( T(I,J), J = 1,S ), I = 1,K )
               ELSE
                  READ ( NIN, FMT = * ) ( ( T(I,J), J = 1,K ), I = 1,S )
               END IF
*              Compute the Cholesky factors.
               CALL MB02CD( JOB, TYPET, K, N, T, LDT, G, LDG, R, LDR, L,
     $                      LDL, CS, LCS, DWORK, LDWORK, INFO )
               IF ( INFO.NE.0 ) THEN
                  WRITE ( NOUT, FMT = 99998 ) INFO
               ELSE
                  WRITE ( NOUT, FMT = 99996 )
                  DO 10  I = 1, N*K
                     WRITE ( NOUT, FMT = 99990 ) ( R(I,J), J = 1, N*K )
   10             CONTINUE
                  IF ( LSAME( JOB, 'R' ) .OR. LSAME( JOB, 'A' ) ) THEN
                     WRITE ( NOUT, FMT = 99995 )
                     IF ( LSAME( TYPET, 'R' ) ) THEN
                        DO 20  I = 1, 2*K
                           WRITE ( NOUT, FMT = 99990 )
     $                           ( G(I,J), J = 1, N*K )
   20                   CONTINUE
                     ELSE
                        DO 30  I = 1, N*K
                           WRITE ( NOUT, FMT = 99990 )
     $                           ( G(I,J), J = 1, 2*K )
   30                   CONTINUE
                     END IF
                  END IF
                  IF ( LSAME( JOB, 'A' ) ) THEN
                     WRITE ( NOUT, FMT = 99994 )
                     DO 40  I = 1, N*K
                        WRITE ( NOUT, FMT = 99990 )
     $                        ( L(I,J), J = 1, N*K )
   40                CONTINUE
                  END IF
*                 Update the Cholesky factors.
                  IF ( LSAME( TYPET, 'R' ) ) THEN
*                    Copy the last block column of R.
                     CALL DLACPY( 'All', N*K, K, R(1,(N-1)*K+1), LDR,
     $                            R(K+1,N*K+1), LDR )
                     CALL MB02DD( JOB, TYPET, K, M, N, T(1,N*K+1), LDT,
     $                            T, LDT, G, LDG, R(1,N*K+1), LDR,
     $                            L(N*K+1,1), LDL, CS, LCS, DWORK,
     $                            LDWORK, INFO )
                  ELSE
*                    Copy the last block row of R.
                     CALL DLACPY( 'All', K, N*K, R((N-1)*K+1,1), LDR,
     $                            R(N*K+1,K+1), LDR )
                     CALL MB02DD( JOB, TYPET, K, M, N, T(N*K+1,1), LDT,
     $                            T, LDT, G, LDG, R(N*K+1,1), LDR,
     $                            L(1,N*K+1), LDL, CS, LCS, DWORK,
     $                            LDWORK, INFO )
                  END IF
                  IF ( INFO.NE.0 ) THEN
                     WRITE ( NOUT, FMT = 99997 ) INFO
                  ELSE
                     WRITE ( NOUT, FMT = 99993 )
                     DO 50  I = 1, S
                        WRITE ( NOUT, FMT = 99990 ) ( R(I,J), J = 1, S )
   50                CONTINUE
                     IF ( LSAME( JOB, 'R' ) .OR. LSAME( JOB, 'A' ) )
     $                       THEN
                        WRITE ( NOUT, FMT = 99992 )
                        IF ( LSAME( TYPET, 'R' ) ) THEN
                           DO 60  I = 1, 2*K
                              WRITE ( NOUT, FMT = 99990 )
     $                              ( G(I,J), J = 1, S )
   60                      CONTINUE
                        ELSE
                           DO 70  I = 1, S
                              WRITE ( NOUT, FMT = 99990 )
     $                              ( G(I,J), J = 1, 2*K )
   70                      CONTINUE
                        END IF
                     END IF
                     IF ( LSAME( JOB, 'A' ) ) THEN
                        WRITE ( NOUT, FMT = 99991 )
                        DO 80  I = 1, S
                           WRITE ( NOUT, FMT = 99990 )
     $                           ( L(I,J), J = 1, S )
   80                   CONTINUE
                     END IF
                  END IF
               END IF
            END IF
         END IF
      END IF
      STOP
*
99999 FORMAT ( ' MB02DD EXAMPLE PROGRAM RESULTS',/1X)
99998 FORMAT ( ' INFO on exit from MB02CD = ',I2)
99997 FORMAT ( ' INFO on exit from MB02DD = ',I2)
99996 FORMAT ( ' The Cholesky factor is ')
99995 FORMAT (/' The inverse generator is ')
99994 FORMAT (/' The inverse Cholesky factor is ')
99993 FORMAT (/' The updated Cholesky factor is ')
99992 FORMAT (/' The updated inverse generator is ')
99991 FORMAT (/' The updated inverse Cholesky factor is ')
99990 FORMAT (20(1X,F8.4))
99989 FORMAT (/' N is out of range.',/' N = ',I5)
99988 FORMAT (/' K is out of range.',/' K = ',I5)
99987 FORMAT (/' M is out of range.',/' M = ',I5)
      END
Program Data
MB02DD EXAMPLE PROGRAM DATA
        3       2       2       A       R
    3.0000    1.0000    0.1000    0.1000    0.2000    0.0500    0.1000    0.0400    0.01   0.02
    1.0000    4.0000    0.4000    0.1000    0.0400    0.2000    0.0300    0.0200    0.03   0.01
Program Results
 MB02DD EXAMPLE PROGRAM RESULTS

 The Cholesky factor is 
   1.7321   0.5774   0.0577   0.0577   0.1155   0.0289
   0.0000   1.9149   0.1915   0.0348  -0.0139   0.0957
   0.0000   0.0000   1.7205   0.5754   0.0558   0.0465
   0.0000   0.0000   0.0000   1.9142   0.1890   0.0357
   0.0000   0.0000   0.0000   0.0000   1.7169   0.5759
   0.0000   0.0000   0.0000   0.0000   0.0000   1.9118

 The inverse generator is 
  -0.2355   0.5231  -0.0642   0.0077   0.0187  -0.0265
  -0.5568  -0.0568   0.0229   0.0060   0.0363   0.0000
   0.5825   0.0000  -0.0387   0.0052   0.0003  -0.0575
  -0.1754   0.5231   0.0119  -0.0265  -0.0110   0.0076

 The inverse Cholesky factor is 
   0.5774   0.0000   0.0000   0.0000   0.0000   0.0000
  -0.1741   0.5222   0.0000   0.0000   0.0000   0.0000
   0.0000  -0.0581   0.5812   0.0000   0.0000   0.0000
  -0.0142   0.0080  -0.1747   0.5224   0.0000   0.0000
  -0.0387   0.0052   0.0003  -0.0575   0.5825   0.0000
   0.0119  -0.0265  -0.0110   0.0076  -0.1754   0.5231

 The updated Cholesky factor is 
   1.7321   0.5774   0.0577   0.0577   0.1155   0.0289   0.0577   0.0231   0.0058   0.0115
   0.0000   1.9149   0.1915   0.0348  -0.0139   0.0957  -0.0017   0.0035   0.0139   0.0017
   0.0000   0.0000   1.7205   0.5754   0.0558   0.0465   0.1145   0.0279   0.0564   0.0227
   0.0000   0.0000   0.0000   1.9142   0.1890   0.0357  -0.0152   0.0953  -0.0017   0.0033
   0.0000   0.0000   0.0000   0.0000   1.7169   0.5759   0.0523   0.0453   0.1146   0.0273
   0.0000   0.0000   0.0000   0.0000   0.0000   1.9118   0.1902   0.0357  -0.0157   0.0955
   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000   1.7159   0.5757   0.0526   0.0450
   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000   1.9118   0.1901   0.0357
   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000   1.7159   0.5757
   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000   1.9117

 The updated inverse generator is 
  -0.5599   0.3310  -0.0305   0.0098   0.0392  -0.0209   0.0191  -0.0010  -0.0045   0.0035
  -0.2289  -0.4091   0.0612  -0.0012   0.0125   0.0182   0.0042   0.0017   0.0014   0.0000
   0.5828   0.0000   0.0027  -0.0029  -0.0195   0.0072  -0.0393   0.0057   0.0016  -0.0580
  -0.1755   0.5231  -0.0037   0.0022   0.0005  -0.0022   0.0125  -0.0266  -0.0109   0.0077

 The updated inverse Cholesky factor is 
   0.5774   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000
  -0.1741   0.5222   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000
   0.0000  -0.0581   0.5812   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000
  -0.0142   0.0080  -0.1747   0.5224   0.0000   0.0000   0.0000   0.0000   0.0000   0.0000
  -0.0387   0.0052   0.0003  -0.0575   0.5825   0.0000   0.0000   0.0000   0.0000   0.0000
   0.0119  -0.0265  -0.0110   0.0076  -0.1754   0.5231   0.0000   0.0000   0.0000   0.0000
  -0.0199   0.0073  -0.0391   0.0056   0.0017  -0.0580   0.5828   0.0000   0.0000   0.0000
   0.0007  -0.0023   0.0122  -0.0265  -0.0110   0.0077  -0.1755   0.5231   0.0000   0.0000
   0.0027  -0.0029  -0.0195   0.0072  -0.0393   0.0057   0.0016  -0.0580   0.5828   0.0000
  -0.0037   0.0022   0.0005  -0.0022   0.0125  -0.0266  -0.0109   0.0077  -0.1755   0.5231

Return to index