Lagrange interpolation 1. 5/28/2016 1 Finding the region with the largest error I have attempted on the left to show a function that has a peak between points 2 and 3. The fact that a point should be placed between these two points can be deduced by calculating the difference between an interpolation to, for example, point 2 using points 1,3,4, and 5 and the known value at point 2. This difference is larger than the difference between the interpolated value at point 4 using points 1,2,3 and 5 and it's the known value. These differences are an estimate of the error at each point. Coding for the Lagrange Polynomial Recall that the code UELAG includes an NSKIP that allows it to skip any desired point. The test codes are RHOT.FOR tfindfun.c while the actual subroutines that find N data points to best represent the function are in Findfun.for and findfun.c. Figure 2 Blow up of the region of the peak showing the points representing the function. The test function for tfindfun.c is a more tame bg Fx 1 7.283I 1 G H0.013 J K f x Equation 2 Results of a test The Fortran test function is bg f x 4274.36e b t / 0.0002 g 2 Equation 1 This was of interest to me because of its ability to practically simulate a delta function. The region of interest is 10 x 10 . The total number of data points is 1000. The first half of these are uniformly spaced. Figure 3 Full scale of Lorentzian with 256 data points between -1 and 19 Figure 4 Blow up clearly showing the difference between a Lorentzian and a Gaussian. Figure 1 Full scale view of the function. Lagrange interpolation 1. Fortran Coding Details 5/28/2016 main program CF90 IF(IERR.NE.0)STOP 'Not enough storage for XDAT,FDAT' 2 Then finally there is the call to finfun. CALL FINFUN(P1,BEGT,ENDT,XDAT,FDAT,NDAT) The test code RHOT.FOR begins with IMPLICIT REAL*8 (A-H,O-Z) COMPLEX*16 P1 EXTERNAL P1 C FOLOWING 4 LINES ARE FOR F77 PARAMETER(NDATM=5000) DIMENSION XDAT(NDATM) COMPLEX*16 FDAT(NDATM) COMMON/PASS/DIFF(NDATM) DIMENSION RREAL(5),IRINT(5) CHARACTER*128 RCHAR(2) CHARACTER*128 NAME CHARACTER*1 F90 C FOLLOWING 2 LINES ARE F90 SPECIFIC CF90 REAL*8 XDAT[ALLOCATABLE](:) CF90 COMPLEX*16 FDAT[ALLOCATABLE](:) DATA F90/'N'/ NINT=1 NREAL=2 NCHAR=1 PRINT*,'BEG END NDAT ' READ(*,*)BEGT,ENDT,NDAT Note 1. P1 is complex. In physics we routinely use complex numbers. The EXTERNAL statement tells the compiler to look for a function outside the main code. This is Fortran's of passing the name of a function as an argument. 2. There are 4 lines specific to Fortran 77. The first is a parameter ndat=5000. This is an attempt to be able to test the code without using a lot of memory or introducing errors by forgetting to change all of the dimensions. The fourth line is a common/pass/. This is an attempt to put all of the data storage into the main code where it is effected by the parameter statement without actually passing the data. In Fortran 90 or C this is created in the subroutine itself. The problem with this external pass is that there is a very real probability of re-using the name or the space, thereby causing a very hard to locate bug. An alternative is to use a parameter statement in the subroutine, but that means changing possibly different parameter names in multiple program segments long after the logic has been forgotten. 3. Then there are two commented out lines that refer to Fortran 90. This is why Fortran will survive; it is a concept adopted from C. 4. Finally there is a print telling the user what to input. Actually the next 5 lines that are commented out are of interest. These allow input from the command line Progdet\GINPUT.htm C ITEST=IPRARG(RREAL,NREAL,IRINT,NINT,RCHAR,NCHAR) CIF(ITEST.NE.0)STOP 'Unable to input data in IPRARG' C NDAT=IRINT(1) IF(F90.EQ.'N'.AND.NDAT.GT.NDATM)STOP ' NDAT > NDATM STOPPING' C BEGT=RREAL(1) C ENDT=RREAL(2) Next come the Fortran 90 implementations of the C allocate routines.Progdet\calloc.htm C FOLLOWING 2 LINES ARE F90 SPECIFIC CF90 ALLOCATE (XDAT(NDAT),FDAT(NDAT),STAT=IERR) There are numerous lines trying to figure out where to write the data and a few defining the function that can be read from the file itself. Findfun FUNCTION FMPOLY(XDAT,FDAT,NDAT,NL,NP,NDATP) C NL is number of data points including the skipped one C XDAT(NP)is the data point to examine. i.e. skip NP IMPLICIT REAL*8 (A-H,O-Z) COMPLEX*16 FDAT(NDAT) PARAMETER (NLAG=12) DIMENSION XDAT(NDAT),ALAG(NLAG) IF(NL.GT.NLAG)THEN PRINT*,' EXCEEDED ALAG DIMENSION IN DIFF' STOP ENDIF IF(NP.GT.NDAT.OR.NDATP.GT.NDAT)THEN PRINT*,' OUT OF DATA BOUNDS IN DIFF' STOP ENDIF MBEG=MAX0(0,NP-1-NL/2) MBEG=MIN0(NDATP-NL,MBEG) Note that the interpolation is centered about np, locate is not used. CALL UELAG(NL,XDAT(NP),MBEG,NP,ALAG,XDAT) POLYL=0 DO I=1,NL POLYL=POLYL+ALAG(I)*ABS(FDAT(I+MBEG)) ENDDO FMPOLY=ABS(ABS(FDAT(NP))-POLYL) IF(FMPOLY.EQ.0)FMPOLY=1D-37 RETURN END The findfun routine itself is SUBROUTINE FINFUN(FUN,BEGR,ENDR,XDAT,FDAT,NDAT) C *** FIRST EVALUATE THE FUNCTION AT N DATA POINTS IMPLICIT REAL*8 (A-H,O-Z) COMPLEX*16 FDAT(NDAT),FUN C FOLLOWING 2 LINES FOR F77, SHOULD BE REPLACED BY F90 PARTS PARAMETER (NMAX=5000) COMMON/PASS/DIFF(NMAX) C FOLLOWING IS USEFUL IN F90 CF90 REAL*8 DIFF[ALLOCATABLE](:) The above plus the 3rd and 4th lines below are the allocation lines for the diff data which really should be specific to this routine. DIMENSION XDAT(NDAT) C FOLLOWING 2 LINES ARE USEFUL IN F90 CF90 ALLOCATE (DIFF(NDAT),STAT=IERR) CF90 IF(IERR.NE.0)STOP 'Finfun Not enough storage for diff' NDBEG=NDAT/2 H=(ENDR-BEGR)/(NDBEG-1) DO I=1,NDBEG XDAT(I)=BEGR+H*(I-1) FDAT(I)=FUN(XDAT(I)) ENDDO Half of the points are used in an equal mesh. One needs a general search before a specific one. DO I=1,NDBEG DIFF(I)=FMPOLY(XDAT,FDAT,NDAT,5,I,NDBEG) IF(I.EQ.1)THEN DIFF(I)=(XDAT(2)-XDAT(1))*DIFF(I) ELSEIF(I.EQ.NDBEG)THEN Lagrange interpolation 1. 5/28/2016 DIFF(I)=(XDAT(NDBEG)-XDAT(NDBEG- 1))*DIFF(I) ELSE DIFF(I)=(XDAT(I+1)-XDAT(I))*DIFF(I) ENDIF ENDDO Note that the size of the region enters into the determination of the relative error. It is at this point that you would return if you were simply checking for typo's in manually typed data. 52 NDTOT=NDBEG AMERR=0 DO I=1,NDTOT IF(ABS(DIFF(I)).GE.AMERR)THEN AMERR=ABS(DIFF(I)) IMAX=I ENDIF ENDDO The reason for finding the diff's was quite simply to find IMAX the location of the largest. IF(IMAX.EQ.1)THEN DL=0 ELSE DL=XDAT(IMAX)-XDAT(IMAX-1) ENDIF IF(IMAX.EQ.NDTOT)THEN DR=0 ELSE DR=XDAT(IMAX+1)-XDAT(IMAX) ENDIF IF(DL.GT.DR)THEN XNEW=.5D0*(XDAT(IMAX-1)+XDAT(IMAX)) ELSE XNEW=.5D0*(XDAT(IMAX)+XDAT(IMAX+1)) IMAX=IMAX+1 ENDIF Note that XNEW is put on the side of IMAX which has the largest delta x. C move the stack up DO I=NDTOT,IMAX,-1 XDAT(I+1)=XDAT(I) FDAT(I+1)=FDAT(I) DIFF(I+1)=DIFF(I) ENDDO Note that moving the stack requires a -1 increment to avoid overwriting values. NDTOT=NDTOT+1 XDAT(IMAX)=XNEW FDAT(IMAX)=FUN(XDAT(IMAX)) N1=MAX(1,IMAX-5) N2=MIN(NDTOT,IMAX+5) DO I=N1,N2 DIFF(I)=FMPOLY(XDAT,FDAT,NDAT,5,I,NDTOT) IF(I.EQ.1)THEN DIFF(I)=(XDAT(2)-XDAT(1))*DIFF(I) ELSEIF(I.EQ.NDTOT)THEN DIFF(I)=(XDAT(NDTOT)-XDAT(NDTOT1))*DIFF(I) ELSE DIFF(I)=(XDAT(I+1)-XDAT(I))*DIFF(I) ENDIF ENDDO Only a few of the differences need to be redefined. IF(NDTOT.LT.NDAT)GOTO 52 RETURN END C programming details main file #include <stdlib.h> #include <stdio.h> #include <math.h> #include <string.h> struct bcmpl {double real;double aimag;}; 3 There is no complex in ansi C. I defined bcmpl for the minimum complex concept. The idea was to use a name that would not interfere with later use of actual complex. A strength of ansi C is that it is almost always available. I believe that a little hand coding of some complex functions is worthwhile to keep the routines always useable. struct bcmpl floren(double x) The function is defined as the structure. Note that so is ret_val below. {double ratio,x0=7.283,w0=0.013; struct bcmpl ret_val; ratio = (x-x0)/w0; ret_val.real = 1/(1+ratio*ratio); ret_val.aimag = 0; return ret_val;} void main(void) {double xdat[1000],fdatr[1000],fdati[1000]; double begt,endt,tabs; int ndat,i; char name[80],oname[80]; FILE *outr,*outi,*outabs; printf("enter begt endt ndat\n"); scanf(" %lg %lg %d",&begt,&endt,&ndat); printf("enter the root file name\n"); scanf("%s",&name); strcpy(oname,name); strcat(oname,"r.out"); outr = fopen(oname, "wt"); printf("real data is in %s\n",oname); … finfun(floren,begt,endt,xdat,fdatr,fdati,ndat); … void finfun(struct bcmpl(*fun)(double),double begr,double endr, double xdat[],double fdatr[],double fdati[],int ndat) Note the C method for passing the name of a function.EXTERNAL.htm … {double *diff; double h,amerr,dl,dr,xnew; struct bcmpl temp; int i,imax,ndtot,ndbeg,nl=5,none,n2; diff = (double *) calloc(ndat, Progdet\calloc.htm sizeof(double)); … temp=(*fun)(xdat[i]); fdatr[i]=temp.real; fdati[i]=temp.aimag;} The actual call to the function. Assignment W rite a code to find F bx 35. gIJ G H 2 K F bx 3.7gIJ 10 expF bx 3.7gIJ 12 expG G H 2 K H 0.02 K bg f x 10 exp How small does the third 10 need to be before this peak cannot be found?