*DECK DPPFA SUBROUTINE DPPFA (AP, N, INFO) C***BEGIN PROLOGUE DPPFA C***PURPOSE Factor a real symmetric positive definite matrix stored in C packed form. C***LIBRARY SLATEC (LINPACK) C***CATEGORY D2B1B C***TYPE DOUBLE PRECISION (SPPFA-S, DPPFA-D, CPPFA-C) C***KEYWORDS LINEAR ALGEBRA, LINPACK, MATRIX FACTORIZATION, PACKED, C POSITIVE DEFINITE C***AUTHOR Moler, C. B., (U. of New Mexico) C***DESCRIPTION C C DPPFA factors a double precision symmetric positive definite C matrix stored in packed form. C C DPPFA is usually called by DPPCO, but it can be called C directly with a saving in time if RCOND is not needed. C (time for DPPCO) = (1 + 18/N)*(time for DPPFA) . C C On Entry C C AP DOUBLE PRECISION (N*(N+1)/2) C the packed form of a symmetric matrix A . The C columns of the upper triangle are stored sequentially C in a one-dimensional array of length N*(N+1)/2 . C See comments below for details. C C N INTEGER C the order of the matrix A . C C On Return C C AP an upper triangular matrix R , stored in packed C form, so that A = TRANS(R)*R . C C INFO INTEGER C = 0 for normal return. C = K if the leading minor of order K is not C positive definite. C C C Packed Storage C C The following program segment will pack the upper C triangle of a symmetric matrix. C C K = 0 C DO 20 J = 1, N C DO 10 I = 1, J C K = K + 1 C AP(K) = A(I,J) C 10 CONTINUE C 20 CONTINUE C C***REFERENCES J. J. Dongarra, J. R. Bunch, C. B. Moler, and G. W. C Stewart, LINPACK Users' Guide, SIAM, 1979. C***ROUTINES CALLED DDOT C***REVISION HISTORY (YYMMDD) C 780814 DATE WRITTEN C 890531 Changed all specific intrinsics to generic. (WRB) C 890831 Modified array declarations. (WRB) C 890831 REVISION DATE from Version 3.2 C 891214 Prologue converted to Version 4.0 format. (BAB) C 900326 Removed duplicate information from DESCRIPTION section. C (WRB) C 920501 Reformatted the REFERENCES section. (WRB) C***END PROLOGUE DPPFA INTEGER N,INFO DOUBLE PRECISION AP(*) C DOUBLE PRECISION DDOT,T DOUBLE PRECISION S INTEGER J,JJ,JM1,K,KJ,KK C***FIRST EXECUTABLE STATEMENT DPPFA JJ = 0 DO 30 J = 1, N INFO = J S = 0.0D0 JM1 = J - 1 KJ = JJ KK = 0 IF (JM1 .LT. 1) GO TO 20 DO 10 K = 1, JM1 KJ = KJ + 1 T = AP(KJ) - DDOT(K-1,AP(KK+1),1,AP(JJ+1),1) KK = KK + K T = T/AP(KK) AP(KJ) = T S = S + T*T 10 CONTINUE 20 CONTINUE JJ = JJ + J S = AP(JJ) - S IF (S .LE. 0.0D0) GO TO 40 AP(JJ) = SQRT(S) 30 CONTINUE INFO = 0 40 CONTINUE RETURN END *DECK DDOT DOUBLE PRECISION FUNCTION DDOT (N, DX, INCX, DY, INCY) C***BEGIN PROLOGUE DDOT C***PURPOSE Compute the inner product of two vectors. C***LIBRARY SLATEC (BLAS) C***CATEGORY D1A4 C***TYPE DOUBLE PRECISION (SDOT-S, DDOT-D, CDOTU-C) C***KEYWORDS BLAS, INNER PRODUCT, LINEAR ALGEBRA, VECTOR C***AUTHOR Lawson, C. L., (JPL) C Hanson, R. J., (SNLA) C Kincaid, D. R., (U. of Texas) C Krogh, F. T., (JPL) C***DESCRIPTION C C B L A S Subprogram C Description of Parameters C C --Input-- C N number of elements in input vector(s) C DX double precision vector with N elements C INCX storage spacing between elements of DX C DY double precision vector with N elements C INCY storage spacing between elements of DY C C --Output-- C DDOT double precision dot product (zero if N .LE. 0) C C Returns the dot product of double precision DX and DY. C DDOT = sum for I = 0 to N-1 of DX(LX+I*INCX) * DY(LY+I*INCY), C where LX = 1 if INCX .GE. 0, else LX = 1+(1-N)*INCX, and LY is C defined in a similar way using INCY. C C***REFERENCES C. L. Lawson, R. J. Hanson, D. R. Kincaid and F. T. C Krogh, Basic linear algebra subprograms for Fortran C usage, Algorithm No. 539, Transactions on Mathematical C Software 5, 3 (September 1979), pp. 308-323. C***ROUTINES CALLED (NONE) C***REVISION HISTORY (YYMMDD) C 791001 DATE WRITTEN C 890831 Modified array declarations. (WRB) C 890831 REVISION DATE from Version 3.2 C 891214 Prologue converted to Version 4.0 format. (BAB) C 920310 Corrected definition of LX in DESCRIPTION. (WRB) C 920501 Reformatted the REFERENCES section. (WRB) C***END PROLOGUE DDOT DOUBLE PRECISION DX(*), DY(*) C***FIRST EXECUTABLE STATEMENT DDOT DDOT = 0.0D0 IF (N .LE. 0) RETURN IF (INCX .EQ. INCY) IF (INCX-1) 5,20,60 C C Code for unequal or nonpositive increments. C 5 IX = 1 IY = 1 IF (INCX .LT. 0) IX = (-N+1)*INCX + 1 IF (INCY .LT. 0) IY = (-N+1)*INCY + 1 DO 10 I = 1,N DDOT = DDOT + DX(IX)*DY(IY) IX = IX + INCX IY = IY + INCY 10 CONTINUE RETURN C C Code for both increments equal to 1. C C Clean-up loop so remaining vector length is a multiple of 5. C 20 M = MOD(N,5) IF (M .EQ. 0) GO TO 40 DO 30 I = 1,M DDOT = DDOT + DX(I)*DY(I) 30 CONTINUE IF (N .LT. 5) RETURN 40 MP1 = M + 1 DO 50 I = MP1,N,5 DDOT = DDOT + DX(I)*DY(I) + DX(I+1)*DY(I+1) + DX(I+2)*DY(I+2) + 1 DX(I+3)*DY(I+3) + DX(I+4)*DY(I+4) 50 CONTINUE RETURN C C Code for equal, positive, non-unit increments. C 60 NS = N*INCX DO 70 I = 1,NS,INCX DDOT = DDOT + DX(I)*DY(I) 70 CONTINUE RETURN END