SUBROUTINE LNCZS 1 ( X, FX, NPTS, NTERMS, X0, FX0, FPX0, WORK, INIT ) C C This subroutine performs Lanczos sigma smoothing C interpolation on the dependent variable array. The C derivative of the interpolate is also calculated. C C X Independent variable array, must be EQUALLY spaced. C FX Dependent variable array. C NPTS Number of points in the above arrays. C NTERMS Number of terms to be used in the smoothing. C X0 Value for which the interpolation is to take place. C FX0 The interpolated value at X0. C FPX0 The derivative of the interpolate at X0. C WORK Storage array dimensioned at least 2*NTERMS+4 in C calling program. Must be maintain from one call C to the next. C INIT Flag to initialize the interpolation. When non-zero, C the interpolate is calculated and C INIT is set to 0. C DIMENSION X(1), FX(1), WORK(1) DATA PI/ 3.1415926535898 / C C - PERFORM THE INITIALIZATION IF REQUIRED. IF( INIT .EQ. 0 ) GO TO 3100 C C - CHECK THE NUMBER OF ARGUMENTS. NARG = 0 CALL NUMARG( NARG ) IF( NARG .EQ. 9 ) GO TO 100 CALL OTSERR( 80 ) STOP C C - CHECK TO SEE IF POINTS ARE EQUALLY SPACED. 100 DX = 0. DO 1000 I=2,NPTS 1000 DX = DX + ( X(I) - X(I-1) ) DX = DX/( ( X(NPTS) - X(1) )/( NPTS - 1 ) ) IF( ABS( DX-1. ) .LE. .001 ) GO TO 1100 CALL OTSERR( 81 ) 1100 INIT = 0 C C - STORE SOME CONSTABLES AWAY AT END OF WORK. A = X(1) WORK( 2*NTERMS+1 ) = A B = X(NPTS) PBA = PI/( B-A ) WORK( 2*NTERMS+2 ) = PBA FXA = FX(1) WORK( 2*NTERMS+3 ) = FXA SLOPE = ( FX(NPTS) - FXA )/( B-A ) WORK( 2*NTERMS+4 ) = SLOPE C C - CALCULATE THE FUNCTION COEFFICIENTS. NMINUS = NPTS-1 DX = ( B-A )/NMINUS DFX = ( FX(NPTS) - FXA )/NMINUS DO 3000 I=1,NTERMS WORK(I) = 0. REMFX = FXA + DFX THETA = I*PBA*DX DTHETA = THETA DO 2000 J=2,NMINUS WORK(I) = WORK(I) + 2.*( FX(J) - REMFX )*SIN( THETA ) REMFX = REMFX + DFX 2000 THETA = THETA + DTHETA C THETA = I*PI/( NTERMS+1 ) SIGMA = SIN( THETA )/THETA WORK(I) = WORK(I)*SIGMA/NMINUS C C - CALCULATE THE INTERPOLATION FUNCTION DERIVATIVE COEFFICIENT. 3000 WORK( NTERMS+I ) = I*PBA*SIGMA*WORK(I) C C - CALCULATE THE INTERPOLATE AND IT'S DERIVATIVE. 3100 A = WORK( 2*NTERMS+1 ) PBA = WORK( 2*NTERMS+2 ) FXA = WORK( 2*NTERMS+3 ) SLOPE = WORK( 2*NTERMS+4 ) C FX0 = 0. FPX0 = 0. THETA = ( X0-A )*PBA DTHETA = THETA C DO 4000 I=1,NTERMS FX0 = FX0 + WORK(I)*SIN( THETA ) FPX0 = FPX0 + WORK( NTERMS+I )*COS( THETA ) 4000 THETA = THETA + DTHETA C FX0 = FX0 + FXA + SLOPE*( X0-A ) FPX0 = FPX0 + SLOPE C RETURN END