NAME
dchdd - downdate an augmented Cholesky decomposition of the
triangular part of an augmented QR decomposition.
SYNOPSIS
SUBROUTINE DCHDD (DA, LDA, N, DX, DZ, LDZ, NZ, DY, DRHO,
DCOS, DSIN, INFO)
SUBROUTINE SCHDD (SA, LDA, N, SX, SZ, LDZ, NZ, SY, SRHO,
SCOS, SSIN, INFO)
SUBROUTINE ZCHDD (ZA, LDA, N, ZX, ZZ, LDZ, NZ, ZY, DRHO,
DCOS, DSIN, INFO)
SUBROUTINE CCHDD (CA, LDA, N, CX, CZ, LDZ, NZ, CY, SRHO,
SCOS, SSIN, INFO)
#include <sunperf.h>
void dchdd(double *r, int ldr, int p, double *dx, double
*dz, int ldz, int nz, double *dy, double *drho,
double *dc, double *s, int *info) ;
void schdd(float *r, int ldr, int p, float *sx, float *z,
int ldz, int nz, float *sy, float *srho, float
*sc, float *s, int *info) ;
void zchdd(doublecomplex *r, int ldr, int p, doublecomplex
*x, doublecomplex *zz, int ldz, int nz, doublecom-
plex *y, doublecomplex *zrho, doublecomplex *zc,
doublecomplex *s, int *info) ;
void cchdd(complex *r, int ldr, int p, complex *cx, complex
*cz, int ldz, int nz, complex *cy, complex *rho,
complex *cc, complex *s, int *info) ;
ARGUMENTS
xA On entry, the upper triangular matrix A. On exit,
A has been downdated. 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.
xX Row to be added to A.
xZ Vectors to be downdated with A.
LDZ Leading dimension on the array Z as specified in a
dimension or type statement. LDZ >= max(1,N).
NZ Number of vectors to be downdated with A. NZ >=
0. If NZ = 0 then Z, Y, and RHO are not used.
xY Scalars for downdating the vectors in Z.
xRHO On entry, the norms of the residual vectors that
are to be downdated. On exit, RHO has been down-
dated. If RHO(i) is negative on entry then it is
not changed.
xCOS Cosines of the transforming rotations.
xSIN Sines of the transforming rotations.
INFO On exit:
INFO = 0 Subroutine completed normally.
INFO = -1 A could not be downdated; all values are
left unchanged.
INFO = 1 Some RHOs could not be downdated; all
RHOs that could not be downdated are changed to
-1.
SAMPLE PROGRAM
PROGRAM TEST
IMPLICIT NONE
C
INTEGER LDA, N, NOPIV, NZ
PARAMETER (N = 4)
PARAMETER (LDA = N)
PARAMETER (NOPIV = 0)
PARAMETER (NZ = 0)
C
DOUBLE PRECISION A(LDA,N), ANULL, C(N), S(N), WORK(N), X(N)
INTEGER I, INFO, IPIVOT(N), J, JOB, NULL
C
EXTERNAL DCHDC, DCHDD
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 and y
C 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, I = 1, N
PRINT 1010, (A(J,I), J = 1, I), (A(I,J), J = I + 1, N)
100 CONTINUE
PRINT 1020
PRINT 1010, ((A(I,J), J = 1, N), I = 1, N)
JOB = NOPIV
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)
ANULL = 0.0D0
NULL = 1
CALL DCHDD (A, LDA, N, X, ANULL, NULL, NZ, ANULL, ANULL, C, S,
$ INFO)
IF (INFO .EQ. 0) THEN
PRINT 1070
PRINT 1080, (C(I), S(I), I = 1, N)
ELSE
PRINT 1090
END IF
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, 'Cosine', 3X, ' Sine')
1080 FORMAT (1X, F6.3, 3X, F6.3)
1090 FORMAT (/1X, 'A cannot be downdated.')
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
Cosine Sine
1.000 0.000
1.000 0.000
1.000 0.000
1.000 0.000
|
Закладки на сайте Проследить за страницей |
Created 1996-2025 by Maxim Chirkov Добавить, Поддержать, Вебмастеру |