8/31/2006 The code for\FromRobmin\solve.for contains changes to the bracketing procedure that were found relevant in fitting nuclear spectra. Origfor.zip contains the original fortran described below. The codes linked to below have been updated and thus changed slightly. The ide is for\brack.wpj. Fortran - for\Brack.for - and C- cpp\Brack.c - bracketing codes, This is an annotated listing of the bracketing codes, followed by an assignment. #include <stdlib.h> C header files always needed, in principle allow you #include <stdio.h> to eliminate unneeded libraries. #include <math.h> double ftan; defines a global variable -- compare to Fortran common double fun1(double x); function definitions char brack(double (*fun)(double),double beg,double endc,double *x1,double *x2, double *f1,double *f2); double anraph(double x1,double f1,double x2, double f2,double (*fun)(double)); double bnraph(double beg,double endc,double (*fun)(double)); The main codes main() {double beg,endc,ftest; all variables must be defined in C int itest; // the test function is FUN1 The // is not always a legal way of making a comment loop: I find that it always pays to loop through a test code. printf(" enter the value of the tangent\n"); The \n is a carriage return line feed scanf("%lg",&ftan); scanf is so bad that ... endc=3.14159/2; beg=-endc; ftest=bnraph(beg,endc,fun1); note the passing of the external function printf("\n tan(%lg) = %lg \n",ftest,ftan); scanf("%d",&itest); if(itest != -1)goto loop; The != is a not = , a logical operator return;} 5 IMPLICIT REAL*8 (A-H,O-Z) required second line of all codes COMMON /PASS/FTAN supplementary method for passing variables EXTERNAL FUN1 note the passing of the external function PRINT*,' ENTER tan value' READ(*,*)FTAN ENDC=3.14159/2 BEG=-ENDC XTEST=BNRAPH(BEG,ENDC,FUN1) PRINT*,' TAN ',XTEST,' = ',FTAN END double fun1(double x) The function tan(x) - the global ftan in C {return tan(x)-ftan;} FUNCTION FUN1(X) The function being zeroed IMPLICIT REAL*8 (A-H,O-Z) COMMON /PASS/FTAN The common is needed to pass ftan FUN1=TAN(X)-FTAN RETURN END char brack(double (*fun)(double),double beg,double endc,double *x1,double *x2, double *f1,double *f2) Note the pointers. {double fact=1.17,alamda,abound,dup,dum,f20,fmult; int i,itest; /*C brack tries to find values x1 and x2 such that fun(x1)*fun(x2)<0 the return is 'y' if this has been is the case and 'n' if not */ alamda = *x1; abound = endc-*x1; f20 = pow(fact,20.); dup = abound/f20; abound = *x1 - beg; dum = abound/f20; *f1=fun(*x1); printf(" x1 = %lg f1 = %lg \n",*x1,*f1); if(*f1 == 0 ) {*x2=*x1; *f2=*f1; return 'f';} fmult=fact; for(i=0;i<20;++i) {*x2=alamda-dum*fmult; *f2=fun(*x2); printf(" x2 = %lg f2 = %lg \n",*x2,*f2); if(*f2 == 0) Note that == is the same as .eq. in fortran not the same as = {*x1=*x2; *f1=*f2; return 'f';} if (*f1 * *f2 < 0)return 'y'; Note the abiguity in the *’s C actually needs a bit more *x2 = alamda + dup * fmult; space than Fortran for this reason *f2=fun(*x2); printf(" x2 = %lg f2 = %lg \n",*x2,*f2); if(*f2 == 0) {*x1=*x2; *f1=*f2; return 'f';} if (*f1 * *f2 < 0)return 'y'; must have a space for readability only fmult *= fact;} No need to say fmult = fmult * fact. return 'y';} The routine below dates from 2001. It finds tries a successively finer grid of points until finally the range between beg and end has been broken into 46 intervals with no sign change. SUBROUTINE BRACK(FUNC,BEG,ENDC,X1,X2,F1,F2,SUCCES) C BRACK TRIES TO FIND VALUES X1 AND X2 SUCH THAT FUNC(X1)*FUNC(X2)<0 C SUCCES IS RETURNED AS 'Y' IF THIS IS THE CASE AND 'N' IF NOT C SUCCES IS RETURNED AS '0' IF FUNC(X1)=0 5 10 IMPLICIT REAL*8 (A-H,O-Z) CHARACTER*1 SUCCES DIMENSION MFRACT(10) DATA MFRACT/2,3,5,7,9,11,13,17,19,23/ JM=1 IM=1 SUCCES='N' X1=BEG F1=FUNC(BEG) IF(F1.EQ.0)THEN SUCCES='0' RETURN ENDIF X2=ENDC CONTINUE F2=FUNC(X2) IF(F2.EQ.0)THEN SUCCES='0' X1=ENDC RETURN ELSEIF(F1*F2.LT.0)THEN SUCCES='Y' RETURN ELSE X2=BEG+(ENDC-BEG)*IM/MFRACT(JM) IM=IM+1 IF(IM.EQ.MFRACT(JM))THEN IF(JM.GE.10)GOTO 10 JM=JM+1 IM=1 ENDIF GOTO 5 ENDIF CONTINUE RETURN END double anraph(double x1,double f1,double x2, double f2,double (*fun)(double)) {double xp[4],xm[4],x,xn,xd,ft,xt,xlower,xupper; int np=0,nm=0,itest; loop5: x = x1-f1*(x2-x1)/(f2-f1); xt=max(fabs(x),1e-12); watch the fabs, abs will not work nor will it give an error if(fabs(x-x1)/xt < 1e-37)return x; loop7: ft = fun(x); note the definition of fun above printf("x = %lg ft = %lg \n",x,ft); printf("x1 = %lg x2=%lg",x1,x2); if(ft*ft < 1e-37)return x; if(f1*ft > 0) {np += 1; nm=0; if(np > 3) // Aitkin's extrapolation positive {xn = xp[3]*xp[1]-xp[2]*xp[2]; xd = xp[3]+xp[1]-2*xp[2]; if(xd != 0)x=xn/xd; else x=xp[3]; xlower = min (x1,x2); xupper = max (x1,x2); if(x < xlower || x > xupper)x = .5 *(x1+x2); np=0; goto loop7;} xp[np]=x; f1=ft; if(x == x1)return x; x1=x; goto loop5;} else {nm += 1; np=0; if(nm > 3) // Aitkin's extrapolation negative {xn = xm[3]*xm[1]-xm[2]*xm[2]; xd = xm[3]+xm[1]-2*xm[2]; if(xd != 0) {x=xn/xd; if(x < x1 || x > x2 ) x = .5*(x1+x2);} else x=xm[3]; xlower = min (x1,x2); xupper = max (x1,x2); if(x < xlower || x > xupper)x = .5 *(x1+x2); nm=0; goto loop7;} else {xm[nm]=x; f2=ft; if(x == x2)return x; x2=x; goto loop5;}}} The multiple parens can be a problem 5 SUBROUTINE NRAF(X1,F1,X2,F2,FUNC) IMPLICIT REAL*8 (A-H,O-Z) DIMENSION XP(3),XM(3) NP=0 NM=0 NCALL=0 X=X1-F1*(X2-X1)/(F2-F1) Newtons method c in robmin, I found that there is a problem in that x2 can be almost x1 while f1 and f2 are different. XT=MAX(ABS(X1),ABS(X2),1D-5) IF(ABS((X1-X2)/XT).LT.1D-12)RETURN 7 FT=FUNC(X) NCALL=NCALL+1 IF(NCALL.GT.500)RETURN PRINT*,' X,FT',X,FT IF(F1*FT.GT.0)THEN NP=NP+1 NM=0 IF(NP.GT.3)THEN XN=XP(3)*XP(1)-XP(2)*XP(2) AITKINS'S EXTRAPOLATION XD=XP(3)+XP(1)-2*XP(2) X=XP(3) IF(XD.NE.0)X=XN/XD XLOWER=MIN(X1,X2) XUPPER=MAX(X1,X2) IF(X.LT.XLOWER.OR.X.GT.XUPPER)X=(X1+X2)/2 NP=0 GOTO 7 ENDIF XP(NP)=X F1=FT IF(X.EQ.X1)THEN X1=X X2=X F2=FT RETURN ENDIF X1=X GOTO 5 ELSE NM=NM+1 NP=0 IF(NM.GT.3)THEN XN=XM(3)*XM(1)-XM(2)*XM(2) AITKINS'S EXTRAPOLATION XD=XM(3)+XM(1)-2*XM(2) X=XM(3) IF(XD.NE.0)X=XN/XD XLOWER=MIN(X1,X2) XUPPER=MAX(X1,X2) IF(X.LT.XLOWER.OR.X.GT.XUPPER)X=(X1+X2)/2 NM=0 GOTO 7 ENDIF XM(NM)=X F2=FT IF(X.EQ.X2)THEN X1=X X2=X RETURN ENDIF X2=X GOTO 5 ENDIF PRINT*,' ANOM RETURN' RETURN END double bnraph(double beg,double endc,double (*fun)(double)) {double x1,x2,f1,f2,ftest; int itest; char succes; // the test function is FUN1 x1=.5*(beg+endc); succes=brack(*fun,beg,endc,&x1,&x2,&f1,&f2); Note the addresses being passed printf(" succes = %c \n",succes); if(succes == 'n') {fprintf(stderr,"brack could find no evidence of a solution \n"); always leave an out fprintf(stderr,"in the range %lg to %lg \n",beg,endc); try to describe the error exit(2);} if(succes == 'f')return x1; ftest=anraph(x1,f1,x2,f2,fun1); return ftest;} FUNCTION BNRAPH(BEG,ENDC,FUN1) IMPLICIT REAL*8 (A-H,O-Z) CHARACTER*1 SUCCES EXTERNAL FUN1 X1=.5*(BEG+ENDC) CALL BRACK(FUN1,BEG,ENDC,X1,X2,F1,F2,SUCCES) IF(SUCCES.NE.'Y')THEN PRINT*,' CANNOT FIND A ZERO CROSSING BETWEEN ',BEG,' AND',ENDC STOP 'STOPPED IN BNRAPH' ENDIF PRINT*,X1,F1 PRINT*,X2,F2 PRINT*,SUCCES IF(SUCCES.EQ.'Y')CALL NRAF(X1,F1,X2,F2,FUN1) PRINT*,' AFTER NRAF X1,F1=',X1,F1 PRINT*,' AFTER NRAF X2,F2=',X2,F2 PRINT*,' FUN1(X1)=',FUN1(X1) BNRAPH=.5D0*(X1+X2) RETURN END Assignment 1 FA T ; T0 , d , p T0 T 1 exp d p Use the brack routine to find T such that FA T ; T0 , d , p 0.975 for T0 = 1.17, d=0.5, p=1. Write the code such that the uniform grid in T(FA) can be found for FA = (j-1d0/2)*.01 for j between 1 and 100. Send me the code. Plot T(FA) – not the line.