appendix. fortran codes - link.springer.com978-3-662-12607-3/1.pdf · appendix. fortran codes ......

48
APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism for badly written) to what we might call ... (W. Gear 1985) The following Fortran codes have been developped for our numerical computations. They can be obtained from the Authors (Section de MatMmati.ques, Case Postale 240, CH-1211 24, Switzerland) on an IBM diskette. Please send 15 Swiss Franks. 1. DopriS Explicit Runge-Kutta code based on the formulas of Dormand and Prince with step size control (see Table 4.6 of Section ll.4). Best method for low tolerances (10-4 to 10- 7 ). SUBROUTINE DOPRI5(N,FCN,X,Y,XKND,KPS,HMAX,H) c ---------------------------------------------------------- c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c NUMERICAL SOLUTION OF A SYSTEM OF FIRST ORDER ORDINARY DIFFERENTIAL EQUATIONS Y'=F(X,Y). THIS IS AN KMBBDDKD RUNGB-KUTTA METHOD OF ORDBR (4)5 DUB TO DORMAND & PRINCB (WITH STKPSIZB CONTROL). C.F. SECTION II.4 INPUT PARAMBTBRS N FCN X XBND Y(N) BPS HMAX H DIMENSION OF TUB SYSTBM (N.LK.51) NAMB (BXTBRNAL) OF SUBROUTINE COMPUTING THB FIRST DERIVATIVE F(X,Y): SUBROUTINE FCN(N,X,Y,F) RBAL*4 X,Y(N),F(N) F(l)=... BTC. INITIAL X-VALUB FINAL X-VALUB (XBND-X POSITIVE OR NBGATIVB) INITIAL VALUBS FOR Y LOCAL TOLERANCE MAXIMAL STBPSIZB INITIAL STBPSIZB GUESS OUTPUT PARAMETERS Y(N) SOLUTION AT XBND BXTBRNAL SUBROUTINE (TO BB SUPPLIED BY TUB USBR) SOLO US THIS SUBROUTINE IS CALLED AFTBR BVBRY SUCCESSFULLY COMPUTED STEP (AND THK INITIAL VALUB): SUBROUTINE SOLOUS (NR,X,Y,N) RBAU4 X,Y(N) FURNISHES THK SOLUTION Y AT THK NR-TH GRID-POINT X (THB INITIAL VALUB IS CON- SIDKRBD AS THB FIRST GRID-POINT). SUPPLY A DUMMY SUBROUTINE, IF THB SOLUTION IS NOT DBSIRKD AT THK INTKRMKDIATK POINTS.

Upload: others

Post on 27-Apr-2020

16 views

Category:

Documents


0 download

TRANSCRIPT

Page 1: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

APPENDIX. FORTRAN CODES ... but the software is in various states of development

from experimental (a euphemism for badly written) to what we might call ... (W. Gear 1985)

The following Fortran codes have been developped for our numerical computations. They can be obtained from the Authors (Section de MatMmati.ques, Case Postale 240, CH-1211 Gen~ve 24, Switzerland) on an IBM diskette. Please send 15 Swiss Franks.

1. DopriS

Explicit Runge-Kutta code based on the formulas of Dormand and Prince with step size control (see Table 4.6 of Section ll.4). Best method for low tolerances (10-4 to 10-7).

SUBROUTINE DOPRI5(N,FCN,X,Y,XKND,KPS,HMAX,H) c ----------------------------------------------------------c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c

NUMERICAL SOLUTION OF A SYSTEM OF FIRST ORDER ORDINARY DIFFERENTIAL EQUATIONS Y'=F(X,Y). THIS IS AN KMBBDDKD RUNGB-KUTTA METHOD OF ORDBR (4)5 DUB TO DORMAND & PRINCB (WITH STKPSIZB CONTROL). C.F. SECTION II.4

INPUT PARAMBTBRS

N FCN

X XBND Y(N) BPS HMAX H

DIMENSION OF TUB SYSTBM (N.LK.51) NAMB (BXTBRNAL) OF SUBROUTINE COMPUTING THB FIRST DERIVATIVE F(X,Y):

SUBROUTINE FCN(N,X,Y,F) RBAL*4 X,Y(N),F(N) F(l)=... BTC.

INITIAL X-VALUB FINAL X-VALUB (XBND-X POSITIVE OR NBGATIVB) INITIAL VALUBS FOR Y LOCAL TOLERANCE MAXIMAL STBPSIZB INITIAL STBPSIZB GUESS

OUTPUT PARAMETERS

Y(N) SOLUTION AT XBND

BXTBRNAL SUBROUTINE (TO BB SUPPLIED BY TUB USBR)

SOLO US THIS SUBROUTINE IS CALLED AFTBR BVBRY SUCCESSFULLY COMPUTED STEP (AND THK INITIAL VALUB):

SUBROUTINE SOLOUS (NR,X,Y,N) RBAU4 X,Y(N)

FURNISHES THK SOLUTION Y AT THK NR-TH GRID-POINT X (THB INITIAL VALUB IS CON­SIDKRBD AS THB FIRST GRID-POINT). SUPPLY A DUMMY SUBROUTINE, IF THB SOLUTION IS NOT DBSIRKD AT THK INTKRMKDIATK POINTS.

Page 2: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

434 Fortran codes

RI!AL*4 K1(51),K2(51),K3(51),K4(51),K5(51),Yl(51),Y(N) LOGICAL RI!JI!CT COMMON/STAT/NFCN,NSTI!P,NACCPT,NRI!JCT

C COMMON STAT CAN Bl! USI!D FOR STATISTICS C NFCN NUMBI!R OF FUNCTION EVALUATIONS C NSTEP NUMBER OF COMPUTED STEPS C NACCPT NUMBER OF ACCEPTED STEPS C NREJCT NUMBER OF REJECTED STEPS

DATA NMAX/3000/,UROUND/5.E-8/ C NMAX MAXIMAL NUMBER OF STEPS C UROUND SMALLEST NUMBER SATISFYING 1.+UROUND>l. C (TO BE ADAPTED BY THE USER)

POSNEG=SIGN(1.,XEND-X) C --- INITIAL PREPARATIONS

HMAX=ABS(HMAX) H=AMINl(AMAX1(1.1!-4,ABS(H)),HMAX) H=SIGN(H,POSNEG) EPS=AMAXl(EPS,7.*UROUND) REJECT=.FALSE. NACCPT=O NREJCT=O NFCN=1 NSTEP=O CALL SOLOUS(NACCPT+1,X,Y,N) CALL FCN(N,X,Y,K1)

C BASIC INTEGRATION STEP IF(NSTEP.GT.NMAX.OR.X+.1*H.EQ.X)GOTO 79 IF((X-XEND)*POSNEG+UROUND.GT.O.) RETURN IF((X+H-XEND)*POSNEG.GT.O.)H=XEND-X NSTI!P=NSTEP+l

C --- THE FIRST 6 STAGES DO 22 I=l,N

22 Y1(I)=Y(I)+H*.2*K1(I) CALL FCN(N,X+.2*H,Yl,K2) DO 23 I=l,N

23 Y1(I)=Y(I)+H*((3./40.)*Kl(I)+(9./40.)*K2(I)) CALL FCN(N,X+.3*H,Yl,K3) DO 24 I=l,N

24 Yl(I)=Y(I)+H*((44./45.)*K1(I)-(56./15.)*K2(1)+(32./9.)*K3(1)) CALL FCN(N,X+.8*H,Y1,K4) DO 25 I=l,N

25 Yl(I)=Y(I)+H*((l9372./656l.)*Kl(I)-(25360./2187.)*K2(1) & +(64448./6561.)*K3(I)-(212./729.)*K4(1))

CALL FCN(N,X+(8./9.)*H,Yl,K5) DO 26 I=1,N '

26 Yl(I)=Y(I)+H*((9017./316B.)*Kl(I)-(355./33.)*K2(1) & +(46732./5247.)*K3(I)+(49./176.)*K4(I)-(5103./18656.)*K5(I))

XPH=X+H CALL FCN(N,XPH,Y1,K2) DO 27 I=l,N

27 Yl(I)=Y(I)+H*((35./384.)*Kl(I)+(500./1113.)*K3(I) & +(125./192.)*K4(I)-(2187./6784.)*K5(I)+(ll./84.)*K2(I))

C --- COMPUTE INTERMEDIATE SUM TO SAVE MEMORY DO 61 I=1,N

61 K2(I)=(71./57600.)*K1(I)-(71./16695.)*K3(I) & +(71./1920.)*K4(I)-(17253./339200.)*K5(I)+(22./525.)*K2(I)

C --- THE LAST STAGE CALL FCN(N,XPH,Y1,K3) DO 28 I=l,N

28 K4(I)=(K2(I)-(1./40.)*K3(I))*H NFCN=NFCN+6

C --- ERROR ESTIMATION ERR=O. DO 41 I=1,N DENOM=AMAX1(l.E-5,ABS(Yl(I)),ABS(Y(I)),2.*UROUND/EPS)

41 ERR=ERR+(K4(I)/DENOM)**2 ERR=SQRT(ERR/FLOAT(N))

Page 3: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Dopri8

C COMPUTATION OF HNEW C WE REQUIRE .2<=HNEW/H<=l0.

FAC=AMAXl(.l,AMIN1(5.,(ERR/EPS)**(l./5.)/.9)) HNEW=H/FAC IF(ERR.LE.EPS)THEN

C --- STEP IS ACCBPTBD NACCPT=NACCPT+l DO 44 I=l,N Kl(I)=K3(I)

44 Y(I)=Yl(I) X=XPH CALL SOLOUS(NACCPT+l,X,Y,N) IF(ABS(HNBW).GT.HMAX)HNEW=POSNEG*HMAX IF(REJECT)HNEW=POSNEG*AMINl(ABS(HNEW),ABS(H)) REJECT=.FALSE.

BLSE C --- STEP IS REJECTED

c ---79

979

c

REJRCT=.TRUE. IF(NACCPT.GR.l)NREJCT=NRRJCT+l

BND IF H=HNEW GOTO 1 FAIL EXIT WRITR(6,979)X FORMAT(' EXIT RETURN END

OF DOPRI5 AT X=',Ell.4)

SUBROUTINE SOLOUS(NRPNTS,X,Y,N) REAL*4 Y(N) RETURN END

2. Dopri8

435

Explicit Runge-Kutta code of high order based on the formulas of Prince and Dorm and with step size control (Table 6.4 of Section 11.6). It is written in double precision and preferable for tolerances between approximately to-7 and to-13. Do not use it below to-16.

SUBROUTINE DOPRI8(N,FCN,X,Y,XEND,EPS,HMAX,H) c ----------------------------------------------------------c c c c c c c c c c c c c c c c c c c c c

NUMERICAL SOLUTION OF A SYSTEM OF FIRST ORDER ORDINARY DIFFERENTIAL EQUATIONS Y'=F(X,Y). THIS IS AN EMBEDDED RUNGE-KUTTA METHOD OF ORDER (7)8 DUE TO DORMAND & PRINCE (WITH STEPSIZE CONTROL). C.F. SECTION II.6

INPUT PARAMETERS

N FCN

X XEND Y(N) BPS HMAX H

DIMENSION OF THE SYSTEM (N.LE.51) NAME (EXTERNAL) OF SUBROUTINE COMPUTING THE FIRST DERIVATIVE F(X,Y):

SUBROUTINE FCN(N,X,Y,F) REAL*8 X,Y(N),F(N) F{l)=... ETC.

INITIAL X-VALUE FINAL X-VALUE (XEND-X POSITIVE OR NEGATIVE) INITIAL VALUES FOR Y LOCAL TOLERANCE MAXIMAL STEPSIZR INITIAL STEPSIZE GUESS

Page 4: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

436 Fortran codes

c c c c c c c c c c c c c c c c

OUTPUT PARAMETERS

Y(N) SOLUTION AT XEND

EXTERNAL SUBROUTINE (TO BE SUPPLIED BY THB USER)

SO LOUT THIS SUBROUTINE IS CALLED AFTBR EVERY SUCCESSFULLY COMPUTED STEP (AND THE INITIAL VALUE):

SUBROUTINE SOLOUT (NR,X,Y,N) REAL*B X,Y(N)

FURNISHES THE SOLUTION Y AT THE NR-TH GRID-POINT X (THB INITIAL VALUB IS CON­SIDERED AS THE FIRST GRID-POINT). SUPPLY A DUMMY SUBROUTINE, IF THB SOLUTION IS NOT DESIRED AT THE INTERMEDIATE POINTS.

c ---------------------------------------------------------IMPLICIT RBAL*B (A-H,O-Z) RBAL*B Kl(5l),K2(5l),K3(5l),K4(5l),K5(5l),K6(5l),K7(51)

*• Y(N), Yl(51) LOGICAL REJECT COMMON/STAT/NFCN,NSTEP,NACCPT,NREJCT

C COMMON STAT CAN BE USED FOR STATISTICS C NFCN NUMBER OF FUNCTION EVALUATIONS C NSTEP NUMBER OF COMPUTED STEPS C NACCPT NUMBER OF ACCEPTED STEPS C NREJCT NUMBER OF REJECTED STEPS

COMMON/COEF/C2,C3,C4,C5,C6,C7,C8,C9,Cl0,Cll,Cl2,Cl3, lA2l,A3l,A32,A4l,A43,A5l,A53,A54,A6l,A64,A65,A7l,A74,A75,A76, lA8l,A84,A85,A86,A87,A9l,A94,A95,A96,A97,A98,Al0l,Al04,Al05,Al06, lAl07,Al08,Al09,Alll,All4,All5,All6,All7,All8,All9,AlllO,Al21, lA124,Al25,Al26,Al27,Al28,Al29,Al2lO,Al2ll,Al3l,Al34,Al35,Al36, lA137,Al38,Al39,Al310,Al3ll,Bl,B6,B7,B8,B9,BlO,Bll,Bl2,Bl3, lBHl,BH6,BH7,BH8,BH9,BHlO,BHll,BH12

DATA NMAX/2000/,UROUND/1.73D-l8/ C NMAX MAXIMAL NUMBER OF STEPS C UROUND SMALLEST NUMBER SATISFYING l.DO+UROUND>l.DO C (TO BB ADAPTED BY THE USBR)

CALL COEFST POSNEG=DSIGN(l.DO,XBND-X)

C --- INITIAL PREPARATIONS HMAX=DABS(HMAX) H=DMINl(DMAXl(l.D-lO,DABS(H)),HMAX) H=DSIGN(H,POSNBG) EPS=DMAXl(EPS,l3.DO*UROUND) RBJBCT=.FALSE. NACCPT=O NRBJCT=O NFCN=O NSTBP=O CALL SOLOUT(NACCPT+l,X,Y,N)

C BASIC INTEGRATION STEP 1 IF(NSTBP.GT.NMAX.OR.X+.03DO*H.EQ.X)GOTO 79

IF((X-XEND)*POSNEG+UROUND.GT.O.DO) RETURN IF((X+H-XEND)*POSNRG.GT.O.DO)H=XEND-X CALL FCN(N,X,Y,Kl)

2 CONTINUE NSTBP=NSTEP+l

C THE FIRST 9 STAGES DO 22 I=l,ll

22 Yl(I)=Y(I)+H*A2l*Kl(I) CALL FCN(N,X+C2*H,Yl,K2) DO 23 I=l,N

23 Yl(I)=Y(I)+H*(A3l*Kl(I)+A32*K2(I)) CALL FCN(N,X+C3*H,Yl,K3) DO 24 I=l,lf

24 Yl(I)=Y(I)+H*(A4l*Kl(I)+A43*K3(I))

Page 5: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

CALL FCN(N,X+C4*H,Yl,K4) DO 25 I=l,N

Dopri8

25 Yl(I)=Y(I)+H*(A5l*Kl(I)+A53*K3(I)+A54*K4(1)) CALL FCN(N,X+C5*H,Yl,K5) DO 26 I=l,N

26 Yl(I)=Y(I)+H*(A6l*Kl(I)+A64*K4(I)+A65*K5(I)) CALL FCN(N,X+C6*H,Yl,K6) DO 27 I=l,N

27 Yl(I)=Y(I)+H*(A7l*Kl(I)+A74*K4(I)+A75*K5(I)+A76*K6(I)) CALL FCN(N,X+C7*H,Yl,K7) DO 28 I=l,N

437

28 Yl(I)=Y(I)+H*(A8l*Kl(I)+A84*K4(I)+A85*K5(I)+A86*K6(I)+A87*K7(I)) CALL FCN(N,X+C8*H,Yl,K2) DO 29 I=l,N

29 Yl(I)=Y(I)+H*(A9l*Kl(I)+A94*K4(I)+A95*K5(I)+A96*K6(I)+A97*K7(I) & +A98*K2(I))

CALL FCN(N,X+C9*H,Yl,K3) DO 30 I=l,N

30 Yl(I)=Y(I)+H*(Al0l*Kl(I)+Al04*K4(I)+Al05*K5(I)+Al06*K6(I) & +Al07*K7(I)+Al08*K2(I)+A109*K3(I))

C --- COMPUTE INTERMEDIATE SUMS TO SAVE MEMORY DO 61 I=l,N YllS=Alll*Kl(I)+All4*K4(I)+All5*K5(I)+All6*K6(I)+All7*K7(I)

& +All8*K2(I)+A119*K3(I) Yl2S=Al2l*Kl(I)+Al24*K4(I)+Al25*K5(I)+Al26*K6(I)+Al27*K7(I)

& +A128*K2(I)+Al29*K3(I) K4(I)=Al3l*Kl(I)+Al34*K4(I)+Al35*K5(I)+Al36*K6(I)+Al37*K7(I)

& +Al38*K2(I)+Al39*K3(I) K5(I)=Bl*Kl(I)+B6*K6(I)+B7*K7(I)+B8*K2(I)+B9*K3(I) K6(I)=BHl*Kl(I)+BH6*K6(I)+BH7*K7(I)+BH8*K2(I)+BH9*K3(I) K2(I)=YllS

61 K3(1)=Yl2S C --- THE LAST 4 STAGES

CALL FCN(N,X+Cl0*H,Y1,K7) DO 31 I=l,N

31 Y1(I)=Y(I)+H*(K2(I)+A1110*K7(I)) CALL FCN(N,X+Cll*H,Yl,K2) XPH=X+H DO 32 I=l,N

32 Yl(I):Y(I)+H*(K3(I)+Al210*K7(I)+Al2ll*K2(I)) CALL FCN(N,XPH,Yl,K3) DO 33 I=l,N

33 Yl(I)=Y(I)+H*(K4(I)+Al310*K7(I)+Al3ll*K2(I)) CALL FCN(N,XPH,Yl,K4) NFCN=NFCN+l3 DO 35 I=l,N K5(I)=Y(I)+H*(K5(I)+BlO*K7(I)+Bll*K2(I)+Bl2*K3(I)+Bl3*K4(I))

35 K6(I)=Y(I)+H*(K6(I)+BHlO*K7(I)+BHll*K2(I)+BH12*K3(I)) C ERROR ESTIMATION

ERR=O.DO DO 41 I=l,N DENOM=DMAXl(l.D-6,DABS(K5(I)),DABS(Y(I)),2.DO*UROUND/EPS)

41 ERR=ERR+((K5(I)-K6(I))/DENOM)**2 ERR=DSQRT(ERR/DFLOAT(N))

C COMPUTATION OF HNEW C WE REQUIRE .333<=HNEW/W<=6.

FAC=DMAXl((l.D0/6.DO),DMIN1(3.DO,(ERR/EPS)**(l.D0/8.D0)/.9DO)) HNEW=H/FAC IF(ERR.GT.EPS)GOTO 51

C --- STEP IS ACCEPTED NACCPT=NACCPT+l DO 44 I=l,N

44 Y(I)=K5{1) X=XPH CALL SOLOUT(NACCPT+l,X,Y,N) IF(DABS(HNEW).GT.HMAX)HNEW=POSNEG*HMAX IF(RBJECT)HNEW=POSNEG*DMINl(DABS(HNEW),DABS(H))

Page 6: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

438

c 51

c ---79

979

c

RllJilCT=.FALS!l. H=HNEW OOTO 1 STEP IS REJECTED REJECT=.TRUE.

Fortran codes

H=HNEW IF(NACCPT.GE.1)NREJCT=NREJCT+1 NFCN=NFCN-1 GOTO 2 FAIL EXIT WRITE(6,979)X FORMAT(' EXIT OF DOPRIB AT X=',D16.7) RETURN END

SUBROUTINE COilFST C THIS SUBROUTIN!l SETS THE COEFFICIENTS FOR THE DORMAND-PRINCE C MllTHOD OF ORDER 8 WITH ERROR ESTIMATOR OF ORDER 7 AND 13 STAGES

IMPLICIT RllAL*B (A-H,O-Z) COMMON/COEF/C2,C3,C4,C5,C6,C7,CB,C9,C10,C11,C12,C13,

& A21,A31,A32,A41,A43,A51,A53,A54,A61,A64,A65,A7l,A74,A75,A76, & A81,A84,A85,A86,A87,A91,A94,A95,A96,A97,A98,A101,A104,A105,A106, & A107,A108,Al09,Al1l,All4,Al15,Al16,A117,All8,A119,AlllO,Al21, & A124,A125,A126,Al27,A128,A129,A1210,Al2ll,Al3l,Al34,Al35,Al36, & Al37,Al38,Al39,Al310,Al3ll,Bl,B6,B7,BB,B9,BlO,Bll,Bl2,Bl3, & BHl,BH6,BH7,BHB,BH9,BHlO,BHll,BH12

C2=l.D0/18.DO C3= 1. D0/12. DO C4=l.D0/8.DO C5=5.D0/16.DO C6=3.D0/8.DO C7=59.D0/400.DO C8=93.D0/200.DO C9=5490023248.D0/971916982l.DO Cl0=13.D0/20.DO Cll=l2011468ll.D0/1299019798.DO Cl2=l.DO Cl3=1. DO A2l=C2 A3l=l.D0/48.DO A32= 1. D0/16. DO A4l=l.D0/32.DO A43=3.D0/32.DO A51=5.DO/l6.DO A53=-75.D0/64.DO A54=-A53 A61=3.D0/80.DO A64=3.D0/16.DO A65=3.D0/20.DO A71=2944384l.D0/614563906.DO A74=77736538.D0/692538347.DO A75=-28693883.DO/ll25.D6 A76=23124283.D0/18.D8 A81=1601614l.D0/9466929ll.DO A84=61564180.D0/158732637.DO A85=22789713.D0/633445777.DO A86=545815736.D0/2771057229.DO A87=-180193667.D0/1043307555.DO A91=39632708.D0/573591083.DO A94=-433636366.D0/683701615.DO A95=-421739975.D0/261629230l.DO A96=10030283l.D0/723423059.DO A97=790204164.D0/839813087.DO A98=800635310.D0/3783071287.DO Al01=246121993.D0/1340847787.DO Al04=-37695042795.DO/l5268766246.DO Al05=-309121744.D0/1061227803.DO

Page 7: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

c

Dopri8

Al06=-12992083.D0/490766935.DO Al07=6005943493.D0/2108947869.DO Al08=393006217.DO/l396673457.DO Al09=12387233l.DO/l001029789.DO Alll=-1028468189.D0/846180014.DO All4=8478235783.D0/508512852.DO All5=1311729495.D0/1432422823.DO All6=-10304129995.D0/1701304382.DO All7=-48777925059.D0/3047939560.DO All8=15336726248.DO/l032824649.DO All9=-4544286818l.D0/3398467696.DO Alll0=3065993473.D0/597172653.DO Al21=185892177.D0/718116043.DO Al24=-3185094517.D0/66710734l.DO Al25=-477755414.D0/1098053517.DO Al26=-703635378.D0/2307392ll.DO Al27=5731566787.DO/l027545527.DO Al28=5232866602.D0/850066563.DO Al29=-4093664535.D0/808688257.DO Al210=3962137247.DO/l805957418.DO Al211=65686358.D0/487910083.DO Al31=403863854.D0/491063109.DO Al34=-5068492393.D0/434740067.DO A135=-411421997.D0/543043805.DO A136=652783627.D0/914296604.DO Al37=11173962825.D0/925320556.DO Al38=-1315899084l.D0/6184727034.DO Al39=3936647629.D0/1978049680.DO A1310=-160528059.D0/685178525.DO A1311=248638103.D0/1413531060.DO Bl=l400545l.D0/335480064.DO B6=-59238493.D0/1068277825.DO B7=181606767.D0/75886773l.DO B8=561292985.D0/797845732.DO B9=-1041891430.D0/1371343529.DO Bl0=760417239.DO/ll51165299.DO Bll=ll8820643.D0/751138087.DO B12=-528747749.D0/2220607170.DO B13=1.D0/4.DO BH1=13451932.D0/455176623.DO BH6=-808719846.D0/976000145.DO BH7=1757004468.D0/564515932l.DO BH8=656045339.D0/265891186.DO BH9=-386757472l.DO/l518517206.DO BH10=465885868.D0/322736535.DO BHll=530ll238.D0/667516719.DO BH12=2.D0/45.DO RETURN END

SUBROUTINE SOLOUT(NSTEP,X,Y,N) IMPLICIT DOUBLE PRECISION (A-H,O-Z) DIMENSION Y(N) RETURN END

439

Page 8: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

440 Fortran codes

3. Odex

Extrapolation code (see Section 11.9) with variable order and vari­able step size. Good for all tolerances, supreme for very high preci­sion (e.g. 10-20 or 10-3~.

SUBROUTINE ODEX (N,FCN,X,Y,XEND,EPS,HMAX,H) c ----------------------------------------------------------c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c

NUMERICAL SOLUTION OF A SYSTEM OF FIRST ORDER ORDINARY DIFFERENTIAL EQUATIONS Y'=F(X,Y). THIS IS AN EXTRAPOLATION-ALGORITHM, BASED ON THE EXPLICIT MIDPOINT RULE (WITH STEPSIZE CONTROL AND ORDER SELECTION). C.F. SECTION II.9

INPUT PARAMETERS

N FCN

X XEND Y(N) EPS HMAX H

DIMENSION OF THE SYSTEM (N.LE.51) NAME (EXTERNAL) OF SUBROUTINE COMPUTING FIRST DERIVATIVE F(X,Y):

SUBROUTINE FCN(N,X,Y,F) REAL*B X,Y(N),F(N) F(l)=... ETC.

INITIAL X-VALUE FINAL X-VALUE (XEND.GT.X) INITIAL VALUES FOR Y LOCAL TOLERANCE MAXIMAL STEPSIZE INITIAL STEPSIZE GUESS

OUTPUT PARAMETERS

Y(N) SOLUTION AT XEND

EXTERNAL SUBROUTINE (TO BE SUPPLIED BY THE USER)

SO LOUT THIS SUBROUTINE IS CALLED AFTER EVERY SUCCESSFULLY COMPUTED STEP (AND THE INITIAL VALUE):

SUBROUTINE SOLOUT (NR,X,Y,N) REAL*B X, Y(N)

FURNISHES THE SOLUTION Y AT THE NR-TH GRID-POINT X (THE INITIAL VALUE IS CON­SIDERED AS THE FIRST GRID-POINT).

THE

SUPPLY A DUMMY SUBROUTINE, IF THE SOLUTION IS NOT DESIRED AT THE INTERMEDIATE POINTS.

c -------------------------------------------·--------------IMPLICIT REAL*B (A-H,O-Z) LOGICAL REJECT,LAST REAL*B Y(N) EXTERNAL FCN COMMON /STAT/NFCN,NSTEP,NACCPT,NREJCT

C COMMON STAT CAN BE USED FOR STATISTICS C NFCN NUMBER OF FUNCTION EVALUATIONS C NSTEP NUMBER Of COMPUTED STEPS C NACCPT NUMBER OF ACCEPTED STEPS C NREJCT NUMBER OF REJECTED STEPS

COMMON /EXTABL/ DZ(5l),T(9,5l),NJ(9),HH(9),W(9),ERR,FAC, A(9),EPSD4,UROUND,FAC1,FAC2,SAFE2

DATA NJ/2,4,6,8,10,12,14,16,18/ DATA A/3.D0,7.D0,13.D0,21.D0,31.D0,43.D0,57.D0,73.D0,91.DO/ DATA NMAX/800/,KM/9/,UROUND/1.73D-18/

C NMAX MAXIMAL NUMBER OF STEPS C UROUND SMALLEST NUMBER SATISFYING l.DO+UROUND>1.DO

Page 9: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Odex

C (TO BR ADAPTED BY THR USER) DATA FAC1/2.D-2/,FAC2/4.DO/,FAC3/.9DO/,FAC4/.BDO/ DATA SAFRl/.65DO/,SAFE2/.94DO/

C --- INITIAL PREPARATIONS EPSD4=RPS*SAFR1 NSTRP=O NRRJCT=O NACCPT=O NFCN=O K=MAX0(3,MINO(B,INT(-DLOG10(EPS)*.6DO+l.5DO))) H=DMINl(H,HMAX,(XRND-X)/2.DO) CALL SOLOUT (NACCPT+l,X,Y,N) RRR=O.DO W(l)=O.DO RRJRCT=.FALSR. LAST=.FALSE.

C --- IS XEND RRACHRD IN THR NEXT STEP? 10 Hl=XEND-X

IF (Hl.LR.UROUND) GO TO 110 H=DMINl(H,H1,HMAX) IF (H.GE.H1-UROUND) LAST=.TRUE. CALL FCN(N,X,Y,DZ) NFCN=NFCN+1

C --- THR FIRST AND LAST STEP IF (NSTEP.EQ.O.OR.LAST) THEN

NSTRP=NSTRP+l DO 20 J=1,K KC=J CALL MIDRX(J,X,Y,H,HMAX,N,FCN)

20 IF (J.GT.1.AND.RRR.LR.RPS) GO TO 60 GO TO 55

RND IF C --- BASIC INTEGRATION STEP

30 CONTINUE NSTEP=NSTEP+1 IF (NSTRP.GR.NMAX) GO TO 120 KC=K-1 DO 40 J=1,KC

40 CALL MIDRX(J,X,Y,H,HMAX,N,FCN) C --- CONVRRGRNCR MONITOR

IF (K.EQ.2.0R.RRJRCT) GO TO 50 IF (RRR.LR.EPS) GO TO 60 IF (RRR/EPS.GT.(DFLOAT(NJ(K+1)*NJ(K))/4.D0)**2) GO TO 100

50 CALL MIDEX(K,X,Y,H,HMAX,N,FCN) KC=K IF (ERR.LR.EPS) GO TO 60

C HOPE FOR CONVRRGRNCR IN LINK K+1 55 IF (ERR/RPS.GT.(DFLOAT(NJ(K+1))/2.D0)**2) GO TO 100

KC=K+1 CALL MIDEX(KC,X,Y,H,HMAX,N,FCN) IF (ERR.GT.EPS) GO TO 100

C STEP IS ACCEPTED 60 X=X+H

DO 70 I=1,N 70 Y(I)=T(1,I)

NACCPT=NACCPT+1 CALL SOLOUT (NACCPT+1,X,Y,N)

C --- COMPUTE OPTIMAL ORDER IF (KC.EQ.2) THEN

KOPT=3 IF (REJECT) KOPT=2 GO TO 80

END IF IF (KC.LE.K) THEN

KOPT=KC IF (W(KC-l).LT.W(KC)*FAC3) KOPT=KC-1 IF (W(KC).LT.W(KC-l)*FAC3) KOPT=MINO(KC+l,KM-1)

441

Page 10: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

442 Fortran codes

ELSE KOPT=KC-1 IF (KC.GT.3.AND.W(KC-2).LT.W(KC-1)*FAC3) KOPT=KC-2 IF (W(KC).LT.W(KOPT)*FAC3) KOPT=MINO(KC,KM-1)

END IF C --- AFTER A REJECTED STEP

80 IF (REJECT) THEN K=MINO(KOPT,KC) H=DMIN1(H,HH(K)) REJECT=.FALSE. GO TO 10

END IF C --- COMPUTE STEPSIZE FOR NEXT STEP

IF (KOPT.LE.KC) THEN H=HH(KOPT)

ELSE IF (KC.LT.K.AND.W(KC).LT.W(KC-1)*FAC4) THEN

H=HH(KC)*A(KOPT+1)/A(KC) ELSE

H=HH(KC)*A(KOPT)/A(KC) END IF

END IF K=KOPT GO TO 10

C --- STEP IS REJECTED 100 K=MINO(K,KC)

IF (K.GT.2.AND.W(K-1).LT.W(K)*FAC3) K=K-1 NREJCT=NREJCT+1 H=HH(K) RllJECT=.TRUil. GO TO 30

C --- SOLUTION EXIT 110 CONTINUE

RETURN C --- FAIL EXIT

c

120 WRITE (6,*) ' MORE THAN ',NMAX,' STEPS RllTURN END

SUBROUTINE MIDEX(J,X,Y,H,HMAX,N,FCN) C THIS SUBROUTINE COMPUTI!S THil J-TH LINil OF THil C EXTRAPOLATION TABLE AND PROVIDES AN ESTIMATION C OF THE OPTIMAL STEPSIZE

IMPLICIT REAL*B (A-H,O-Z) llXTERNAL FCN REAL*B Y(N),DY(51),YH1(51),YH2(51) COMMON /STAT/NFCN,NSTEP,NACCPT,NREJCT COMMON /EXTABL/ DZ(51),T(9,51),NJ(9),HH(9),W(9),ERR,FAC,

1 A(9),EPSD4,UROUND,FAC1,FAC2,SAFE2 HJ=H/DFLOAT(NJ(J))

C --- EULER STARTING STEP DO 30 I=1,N YH1(I)=Y(I)

30 YH2(I)=Y(I)+HJ*DZ(I) C EXPLICIT MIDPOINT RULil

M=NJ(J)-1 DO 35 MM=1,M CALL FCN(N,X+HJ*DFLOAT(MM),YH2,DY) DO 35 I=1,N YS=YH1(1) YH1(I)=YH2(I)

35 YH2(I)=YS+2.DO*HJ*DY(I) C --- FINAL SMOOTHING STI!P

CALL FCN(N,X+H,YH2,DY) DO 40 I=1,N

40 T(J,I)=(YHl(I)+YH2(I)+HJ*DY(I))/2.DO NFCN=NFCN+NJ(J)

Page 11: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Odex

C --- POLYNOMIAL EXTRAPOLATION IF (J.EQ.1) RETURN DO 60 L=J,2,-1 FAC=(DFLOAT(NJ(J))/DFLOAT(NJ(L-1)))**2-1.DO DO 60 I=1,N T(L-1,I)=T(L,I)+(T(L,I)-T(L-1,I))/FAC

60 CONTINUE ERR=O.DO DO 65 I=1,N

C SCALING SCAL=DMAX1(DABS(Y(I)),DABS(T(1,I)),1.D-6,UROUND/EPSD4)

65 BRR=ERR+((T(1,I)-T(2,I))/SCAL)**2 BRR=DSQRT(BRR/DFLOAT(N))

C COMPUTE OPTIMAL STBPSIZBS

c

EXP0=1.DO/DFLOAT(2*J-1) FACMIN=FAC1**EXPO FAC=DMIN1(FAC2/FACMIN,DMAX1(FACMIN,(BRR/EPSD4)**EXPO/SAFE2)) FAC=1. DO/FAC HH(J)=DMIN1(H*FAC,HMAX) W(J)=A(J)/HH(J) RETURN END

SUBROUTINE SOLOUT (NRPNTS,X,Y,N) IMPLICIT RBAL*B (A-H,O-Z) RBAL*B Y(N) RETURN END

4. Odex2

443

Extrapolation code (see Section 11.13) with variable order and variable step size for second order differential systems of the form y " = f (x , y). Good for all tolerances.

SUBROUTINE ODEX2 (N,FCN,X,Y,YP,XBND,BPS,HMAX,H) c ----------------------------------------------------------c c c c c c c c c c c c c c c c c c c c c c c c c c c c

NUMERICAL SOLUTION OF A SYSTEM OF SECOND ORDER ORDINARY DIFFERENTIAL EQUATIONS Y"=F(X,Y). THIS IS AN EXTRAPOLATION-ALGORITHM, BASED ON THE EXPLICIT MIDPOINT RULE (WITH STEPSIZB CONTROL AND ORDER SELECTION). C.F. SECTION II.13

INPUT PARAMETERS

N FCN

X XBND Y(N) YP(N) BPS HMAX H

DIMENSION OF THE SYSTEM (N.LB.51) NAME (EXTERNAL) OF SUBROUTINE COMPUTING SECOND DERIVATIVE F(X,Y):

SUBROUTINE FCN(N,X,Y,F) RBAL*B X,Y(N),F(N) F (l) =. . . ETC.

INITIAL X-VALUE FINAL X-VALUE (XBND.OT.X) INITIAL VALUES FOR Y INITIAL VALUES FOR Y' LOCAL TOLERANCE MAXIMAL STEPSIZE INITIAL STEPSIZB OUBSS

OUTPUT PARAMETERS

Y(N) YP(N)

SOLUTION AT XBND DERIVATIVE OF SOLUTION AT XEND

THE

Page 12: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

444 Fortran codes

c c c c c c c c c c c c

EXTERNAL SUBROUTINE (TO BE SUPPLIED BY THE USER)

SOLUT2 THIS SUBROUTINE IS CALLED AFTER EVERY SUCCESSFULLY COMPUTED STEP (AND THE INITIAL VALUE):

SUBROUTINE SOLUT2 (NR,X,Y,YP,N) REAL*8 X,Y(N),YP(N)

FURNISHES THE SOLUTION (Y,YP) AT THE NR-TH GRID-POINT X (THE INITIAL VALUE IS CON­SIDERED AS THE FIRST GRID-POINT). SUPPLY A DUMMY SUBROUTINE, IF THE SOLUTION IS NOT DESIRED AT THE INTERMEDIATE POINTS.

c ---------------------------------------------------------

c c c c c

1

c c c

c ---

IMPLICIT REAL*8 (A-H,O-Z) LOGICAL REJECT,LAST REAL*8 Y(N),YP(N) EXTERNAL FCN COMMON /STAT/NFCN,NSTEP,NACCPT,NREJCT

COMMON STAT CAN BE USED FOR STATISTICS NFCN NUMBER OF FUNCTION EVALUATIONS NSTEP NUMBER OF COMPUTED STEPS NACCPT NUMBER OF ACCEPTED STEPS NREJCT NUMBER OF REJECTED STEPS

COMMON /EXTABL/ DZ(5l),T(9,5l),TP(9,51),NJ(9),HH(9),W(9),ERR,FAC, A(9),EPSD4,UROUND,FAC1,FAC2,SAFE2

DATA NJ/2,4,6,8,10,12,14,16,18/ DATA A/2.D0,4.D0,7.D0,11.D0,16.D0,22.D0,29.D0,37.D0,46.DO/ DATA NMAX/800/,KM/9/,UROUND/1.73D-18/

NMAX MAXIMAL NUMBER OF STEPS UROUND SMALLEST NUMBER SATISFYING 1.DO+UROUND>1.DO

(TO BE ADAPTED BY THE USER) DATA FAC1/2.D-2/,FAC2/4.DO/,FAC3/.9DO/,FAC4/.8DO/ DATA SAFE1/.65DO/,SAFE2/.94DO/

INITIAL PREPARATIONS EPSD4=EPS*SAFE1 NSTEP=O NREJCT=O NACCPT=O NFCN=O K=MAX0(3,MIN0(8,INT(-DLOG10(EPS)*.6D0+1.5DO))) H=DMIN1(B,BMAX,(XEND-X)/2.DO) CALL SOLUT2 (NACCPT+1,X,Y,YP,N) ERR=O.DO W(1)=0.DO REJI!CT=.FALSE. LAST=.FALSE.

C IS XEND REACHED IN THI! NEXT STEP? 10 H1=XEND-X

IF (H1.LE.UROUND) GO TO 110 H=DMIN1(H,H1,HMAX) IF (H.GE.H1-UROUND) LAST=.TRUI!. CALL FCN(N,X,Y,DZ) NFCN=NFCN+1

C --- THE FIRST AND LAST STEP IF (NSTEP.EQ.O.OR.LAST) THEN

NSTEP=NSTEP+1 DO 20 J=1,K KC=J CALL STOERM(J,X,Y,YP,H,HMAX,N,FCN)

20 IF (J.GT.1.AND.ERR.LE.EPS) GO TO 60 GO TO 55

END IF C BASIC INTEGRATION STEP

30 CONTINUE NSTEP=NSTEP+1 IF (NSTEP.GE.NMAX) GO TO 120 KC=K-1 DO 40 J=1,KC

Page 13: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Odex2

40 CALL STOERM(J,X,Y,YP,H,HMAX,N,FCN) C CONVERGENCE MONITOR

IF (K.EQ.2.0R.REJRCT) GO TO 50 IF (ERR.LE.EPS) GO TO 60 IF (ERR/EPS.GT.(DFLOAT(NJ(K+1}*NJ(K)}/4.D0)**2) GO TO 100

50 CALL STOERM(K,X,Y,YP,H,HMAX,N,FCN) KC=K IF (ERR.LE.RPS) GO TO 60

C --- HOPE FOR CONVERGENCE IN LINE K+l 55 IF (BRR/RPS.GT.(DFLOAT(NJ(K+l))/2.D0)**2) GO TO 100

KC=K+l CALL STOERM(KC,X,Y,YP,H,HMAX,N,FCN) IF (ERR.GT.EPS) GO TO 100

C STEP IS ACCEPTED 60 X=X+H

DO 70 l=l,N YP(I)=TP(l,l)

70 Y(I)=T(l,l) NACCPT=NACCPT+l CALL SOLUT2 (NACCPT+1,X,Y,YP,N)

C --- COMPUTE OPTIMAL ORDER IF (KC.EQ.2) THEN

KOPT=3 IF (REJECT) KOPT=2 GO TO 80

END IF IF (KC.LE.K) THEN

KOPT=KC IF (W(KC-l).LT.W(KC)*FAC3) KOPT=KC-1 IF (W(KC).LT.W(KC-l)*FAC3) KOPT=MINO(KC+1,KM-1)

ELSE KOPT=KC-1 IF (KC.GT.3.AND.W(KC-2}.LT.W(KC-1)*FAC3) KOPT=KC-2 IF (W(KC).LT.W(KOPT)*FAC3) KOPT=MINO(KC,KM-1)

END IF C --- AFTER A REJECTED STEP

80 IF (REJECT) THEN K=MINO(KOPT,KC) H=DMIN1(H,HH(K)) REJECT=.FALSE. GO TO 10

END IF C --- COMPUTE STEPSIZE FOR NEXT STEP

IF (KOPT.LE.KC) THEN H=HH(KOPT)

ELSE IF (KC.LT.K.AND.W(KC).LT.W(KC-1)*FAC4) THEN

H=HH(KC)*A(KOPT+1)/A(KC) ELSE

H=HH(KC)*A(KOPT)/A(KC} END IF

END IF K=KOPT GO TO 10

C --- STEP IS REJECTED 100 K=MINO(K,KC)

IF (K.GT.2.AND.W(K-1).LT.W(K)*FAC3) K=K-1 NREJCT=NREJCT+l H=HH(K) REJECT=.TRUE. GO TO 30

C --- SOLUTION EXIT 110 CONTINUE

RETURN C --- FAIL EXIT

c

120 WRITE (6,*) ' MORE THAN ',NMAX,' STEPS RETURN END

445

Page 14: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

446 Fortran codes

SUBROUTINE STOERM(J,X,Y,YP,H,HMAX,N,FCN) C THIS SUBROUTINE COMPUTES THE J-TH LINE OF THE C EXTRAPOLATION TABLE AND PROVIDES AN ESTIMATION C OF THE OPTIMAL STEPSIZE

IMPLICIT REAL*8 (A-H,O-Z) EXTERNAL FCN REAL*8 Y(N),YP(N),DY(5l),YH1(5l),ZH1(51) COMMON /STAT/NFCN,NSTEP,NACCPT,NREJCT COMMON /EXTABL/ DZ(5l),T(9,5l),TP(9,5l),NJ(9),HH(9),W(9),ERR,FAC,

A(9),EPSD4,UROUND,FACl,FAC2,SAFE2 HJ=H/DFLOAT(NJ(J)) HJ2=HJ*2.DO

C --- EULER STARTING STEP DO 30 I=l,N YH1 (I) =Y( I)

30 ZH1(I)=YP(I)+HJ*DZ(I) C --- EXPLICIT MIDPOINT (STOERMER) RULE

M=NJ(J)/2-1 IF (J.EQ.l) GO TO 37 DO 35 MM=1,M DO 33 I=1,N

33 YHl(I)=YH1(I)+HJ2*ZHl(I) CALL FCN(N,X+HJ2*DFLOAT(MM),YHl,DY) DO 35 I=1,N

35 ZH1(I)=ZHl(I)+HJ2*DY(I) C --- FINAL STEP

37 CONTINUE DO 40 I=l,N

40 YHl(I)=YHl(I)+HJ2*ZHl(I) CALL FCN(N,X+H,YHl,DY) DO 43 I=l,N T(J, I)=YHl(I)

43 TP(J,I)=ZH1(I)+HJ*DY(I) NFCN=NFCN+M+l

C --- POLYNOMIAL EXTRAPOLATION IF (J.EQ.1) RETURN DO 60 L=J,2,-1 FAC=(DFLOAT(NJ(J))/DFLOAT(NJ(L-1)))**2-l.DO DO 60 I=l,N T(L-1,I)=T(L,I)+{T(L,I)-T(L-1,1))/FAC TP(L-1,I)=TP(L,I)+(TP(L,I)-TP(L-l,I))/FAC

60 CONTINUE ERR=O.DO DO 65 I=1,N

C --- SCALING SCAL=DMAXl(DABS(Y(I)),DABS(T(l,I)),l.D-6,UROUND/EPSD4) SCALP=DMAXl(DABS(YP(I)),DABS{TP(l,I)),l.D-6,UROUND/EPSD4)

65 ERR=ERR+((T(l,I)-T(2,I))/SCAL)**2+((TP(l,I)-TP(2,I))/SCALP)**2 ERR=DSQRT(ERR/DFLOAT(N*2))

C --- COMPUTE OPTIMAL STEPSIZES

c

EXPO=l.DO/DFLOAT(2*J-l) FACMIN=FACl**EXPO FAC=DMINl(FAC2/FACMIN,DMAXl(FACMIN,(ERR/EPSD4)**EXPO/SAFE2)) FAC=l.DO/FAC HH(J)=DMIN1(H*FAC,HMAX) W(J)=A(J)/HH(J) RETURN END

SUBROUTINE SOLUT2 (NRPNTS,X,Y,YP,N) IMPLICIT REAL*8 (A-H,O-Z) REAL*8 Y(N),YP(N) RETURN END

Page 15: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Doprin 447

S. Doprln

Explicit Runge-Kutta-Nystr6m code based on the formulas of Dormand and Prince with step size control (see Table 13.4 of Section 2.13) for second order differential systems of the form y" == f (x ,y ).

SUBROUTINE DOPRIN(N,FCN,X,Y,YP,XEND,EPS,HMAX,H) c ----------------------------------------------------------c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c c

NUMERICAL SOLUTION OF A SYSTEM OF SECOND ORDER ORDINARY DIFFERENTIAL EQUATIONS Y"=F(X,Y). THIS IS AN EMBEDDED NYSTROEM METHOD OF ORDER (6)7 DUE TO DORMAND & PRINCE (WITH STEPSIZE CONTROL) C.F. SECTION II.l3

INPUT PARAMETERS

N FCN

X XEND Y(N) YP(N) EPS HMAX H

DIMENSION OF THE SYSTEM (N.LE.51) NAME (EXTERNAL) OF SUBROUTINE COMPUTING SECOND DERIVATIVE F(X,Y):

SUBROUTINE FCN(N,X,Y,F) REAL*8 X,Y(N),F(N) F(l)=... ETC.

INITIAL X-VALUE FINAL X-VALUE (XEND.GT.X) INITIAL VALUES FOR Y INITIAL VALUES FOR Y' LOCAL TOLERANCE MAXIMAL STEPSIZE INITIAL STEPSIZE GUESS

OUTPUT PARAMETERS

Y(N) YP(N)

SOLUTION AT XEND DERIVATIVE OF SOLUTION AT XEND

EXTERNAL SUBROUTINE (TO BE SUPPLIED BY THE USER)

SOLUT2 THIS SUBROUTINE IS CALLED AFTER EVERY SUCCESSFULLY COMPUTED STEP (AND THE INITIAL VALUE):

SUBROUTINE SOLUT2 (NR,X,Y,YP,N) REAL*8 X,Y(N),YP(N)

THE

FURNISHES THE SOLUTION (Y,YP) AT THE NR-TH GRID-POINT X (THE INITIAL VALUE IS CON­SIDERED AS THE FIRST GRID-POINT). SUPPLY A DUMMY SUBROUTINE, IF THE SOLUTION IS NOT DESIRED AT THE INTERMEDIATE POINTS.

c ---------------------------------------------------------IMPLICIT REAL*8 (A-H,O-Z) REAL*8 K0(5l),Kl(5l),K2(5l),K3(5l),K4(5l),Yl(5l),Y(N),YP(N) LOGICAL REJECT COMMON/STAT/NFCN,NSTEP,NACCPT,NREJCT

C COMMON STAT CAN BE USED FOR STATISTICS C NFCN NUMBER OF FUNCTION EVALUATIONS C NSTEP NUMBER OF COMPUTED STEPS C NACCPT NUMBER OF ACCEPTED STEPS C NREJCT NUMBER OF REJECTED STEPS

DATA NMAX/2000/,UROUND/1.73D-18/ C NMAX MAXIMAL NUMBER OF STEPS C UROUND SMALLEST NUMBER SATISFYING l.DO+UROUND>l.DO C (TO BE ADAPTED BY THE USER)

ALPHl=.lDO ALPH2=.2DO

Page 16: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

448

ALPH3=3.D0/8.DO ALPH4=.5DO SQ2l=DSQRT(2l.DO) ALPH5=(7.DO-SQ21)/14.DO ALPH6=(7.DO+SQ21)/14.DO C0=.05DO C4=16.D0/45.DO C5=49.D0/180.DO Gl0=l.D0/200.DO G20= 1. DO/ 150. DO G2l=l.D0/75.DO G30=17l.D0/8192.DO G31=45.D0/4096.DO G32=315.D0/8192.DO G40=5.D0/288.DO G41=25.D0/528.DO G42=25.D0/672.DO

Fortran codes

G43=16.D0/693.DO G50=(1003.D0-205.DO*S021)/12348.DO G51=(-18775.D0+4325.DO*S021)/90552.DO G52=(15600.D0-3425.DO*S021)/43218.DO G53=(-46208.DO+l0112.DO*S021)/237699.DO G54=(34ll.D0-745.DO*SQ21)/24696.DO G60=(793.DO+l87.DO*S02l)/12348.DO G61=(-8275.D0-2825.DO*SQ21)/90552.DO G62=(26100.D0+6175.DO*S021)/43218.DO G63=-(1905280.D0+483712.DO*S021)/9745659.DO G64=(3327.D0+797.DO*S021)/24696.DO G65=-(58l.DO+l27.DO*S021)/1722.DO G70=(-157.D0+3.DO*SQ21)/378.DO G71=(3575.D0-250.DO*SQ21)/2772.DO G72=-(21900.D0+1375.DO*S02l)/3969.DO G73=(1168640.D0+23040.DO*SQ21)/596673.DO G74=-(1353.D0+26.DO*SQ21)/2268.DO G75=(12439.D0+2639.DO*S021)/4428.DO G76=(35.D0-7.DO*S021)/36.DO G80=.05DO G84=8.D0/45.DO G85=(49.D0+7.DO*S021)/360.DO G86=(49.D0-7.DO*S021)/360.DO POSNEG=DSIGN(l.DO,XEND-X)

C --- INITIAL PREPARATIONS HMAX=DABS(HMAX) H=DMINl(DMAXl(l.D-B,DABS(H)),HMAX) H=DSIGN(H,POSNEG) EPS=DMAXl(EPS,9.DO*UROUND) RBJBCT=.FALSB. NACCPT=O NREJCT=O NFCN=l NSTBP=O CALL SOLUT2(NACCPT+l,X,Y,YP,N) CALL FCN(N,X,Y,KO)

C -------- BASIC INTEGRATION STEP ---------------------1 IF(NSTEP.GT.NMAX.OR.X+.05DO*H.EQ.X)GOTO 79

IF((X-XEND)*POSNEG+UROUND.GT.O.DO) RETURN IF((X+H-XEND)*POSNRG.GT.O.DO)H=XEND-X HP2=H*H NSTEP=NSTEP+l

C THE FIRST 5 STAGES DO 21 I=l,N

21 Yl(I)=Y(I)+ALPHl*H*YP(I)+HP2*GlO*KO(I) CALL FCN(N,X+ALPHl*H,Yl,Kl) DO 22 I=l,N

22 Yl(I)=Y(I)+ALPH2*H*YP(I)+HP2*(G20*KO(I)+G2l*Kl(I)) CALL FCN(N,X+ALPH2*H,Yl,K2) DO 23 I=l,N

Page 17: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

23

24

25

c

61 c ---

26

27

Doprin

Yl(I)=Y(I)+ALPH3*H*YP(I)+HP2*(G30*KO(I)+G3l*Kl(I)+G32*K2(1)) CALL FCN(N,X+ALPH3*H,Yl,K3) DO 24 l=l,N Yl(l)=Y(I)+ALPH4*H*YP(I)+HP2*(G40*KO(I)+G4l*Kl(l)+G42*K2(1)+

& G43*K3(I)) CALL FCN(N,X+ALPH4*H,Yl,K4) DO 25 I=l,N Yl(I)=Y(I)+ALPH5*H*YP(I)+HP2*(G50*KO(I)+G5l*Kl(I)+G52*K2(I)+

& G53*K3(I)+G54*K4(1)) COMPUTE INTERMEDIATE SUM TO SAVE MEMORY DO 61 I=l,N YlS=G60*KO(I)+G6l*Kl(I)+G62*K2(I)+G63*K3(I)+G64*K4(I) K3(I)=G70*KO(I)+G7l*Kl(I)+G72*K2(I)+G73*K3(I)+G74*K4(I) K2 (I) =YlS THE LAST 4 STAGES CALL FCN(N,X+ALPH5*H,Yl,Kl) DO 26 I=l,N Yl(I)=Y(I)+ALPH6*H*YP(I)+HP2*(K2(I)+G65*Kl(I)) CALL FCN(N,X+ALPH6*H,Yl,K2) DO 27 I=l,N Yl(I)=Y(I)+H*YP(I)+HP2*(K3(I)+G75*Kl(I)+G76*K2(1)) XPH=X+H CALL FCN{N,XPH,Yl,K3)

449

28

30

DO 28 I=l,N Yl(I)=Y(I)+H*YP(I)+HP2*(G80*KO(I)+G84*K4(I)+G85*Kl(I)+G86*K2(I)) DO 30 I=l,N K4(I)=YP(I)+H*(CO*(KO(I)+K3(I))+C4*K4(I)+C5*(Kl(I)+K2(I)))

33

c ---

41

c c

CALL FCN(N,XPH,Yl,Kl) DO 33 I=l,N K2(I)=HP2*(Kl(I)-K3(I))/20.DO NFCN=NFCN+8 ERROR ESTIMATION ERR=O.DO DO 41 I=l,N DENOM=DMAXl(l.D-6,DABS(Yl(I)),DABS(Y(I)),2.DO*UROUND/EPS) ERR=ERR+(K2(1)/DENOM)**2 ERR=DSQRT(ERR/DFLOAT(N)) COMPUTATION OF HNEW WE REQUIRE .2<=HNEW/H<=l0.

FAC=DMAXl(.lDO,DMIN1(5.DO,(ERR/EPS)**(l.D0/7.D0)/.9DO)) HNRW=H/F"AC

IF(ERR.LE.EPS)THEN C --- STEP IS ACCEPTED

NACCPT=NACCPT+l DO 44 I=1,N YP(I)=K4(I)

44

c ---

c ---79

979

KO(I)=Kl(I) Y(I)=Y1(I) X=XPH CALL SOLUT2(NACCPT+l,X,Y,YP,N) IF(DABS(HNEW).GT.HMAX)HNEW=POSNEG*HMAX IF(REJECT)HNEW=POSNEG*DMINl(DABS(HNEW),DABS(H)) RI!JI!CT=.FALSI!.

ELSE STI!P IS REJECTED

REJECT=.TRUE. IF(NACCPT.GE.1)NREJCT=NRI!JCT+1

I!ND IF H=HNEW GOTO 1 FAIL EXIT WRITE(6,979)X FORMAT(' EXIT OF DOPRIN AT X=',Dl6.7) RETURN I!ND

Page 18: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

450

c

Fortran codes

SUBROUTINE SOLUT2 (NRPNTS,X,Y,YP,N) IMPLICIT RBAL*B (A-H,O-Z) RBAL*B Y(N),YP(N) RETURN END

6. Retard

Modification of the code DOPRI5 for delay differential equations

(see Section ll.15). A sample calling program is included. The sub­

routines STORE and YLAG are also useful for dense output and graphics.

C ------- SAMPLE CALLING PROGRAM FOR RETARD ----------C SOLVING PROBLEM (15.12) WITH SAME INITIAL CONDITIONS C AS FOR TABLE 15.1.

D !MENS ION Y (l) COMMON/POSITS/IFIRST,LAST,XO,XLAST,IPOS,DISC COMMON/STAT/NFCN,NSTEP,NACCPT,NREJCT EXTERNAL FCN XO=O. LAST=O H=0.5 Y(l)=0.1 DO 1 I=1,10

X=FLOAT(I-1) XEND=FLOAT (I) EPS=1.E-6 HMAX= l. CALL RETARD(l,FCN,X,Y,XEND,EPS,HMAX,H) WRITB(S,*)X,Y(l) WRITE(6,*)' COMMON STAT:' ,NFCN,NSTEP,NACCPT,NREJCT CONTINUE

STOP END

SUBROUTINE FCN(N,X,Y,F) DIMENSION Y(N),F(N) EXTERNAL PHI A=l.4 F(l) =(A-YLAG(l, X-l., PHI) )*Y( 1) RETURN END

REAL FUNCTION PHI(I,X) IF(I.RQ.1)PHI=O. RETURN END

SUBROUTINE RBTARD(N,FCN,X,Y,XBND,EPS,HMAX,H)

c ----------------------------------------------------------c c c c c c c c c c c c c c

NUMERICAL SOLUTION OF A SYSTEM OF FIRST ORDER RETARDED DIFFERENTIAL EQUATIONS Y'=F(X,Y(X),Y(X-TAU), .. ). 1

THIS IS BASED ON AN EMBEDDED RUNGE-KUTTA METHOD OF ORDER (4)5

DUE TO DORMAND & PRINCE (WITH STEPSIZE CONTROL). C.F. SECTIONS II.5 AND 11.15

INPUT PARAMETERS

N FCN

DIMENSION OF THE SYSTEM (N.LR.51) NAME (EXTERNAL) OF SUBROUTINE COMPUTING FIRST DERIVATIVE F(X,Y):

SUBROUTINE FCN(N,X,Y,F) REAL*4 X,Y(N),F(N) EXTERNAL PHI

THE

Page 19: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

c c c c c c c c c c c c c c c c c

Retard

F(l)=-YLAG(l,X-l.,PHI)+ ... F(2)=... I!TC.

WHI!RB "PHI" IS THI! (I!XTI!RNAL) A RI!AL FUNCTION COMPUTING THI! I-TH COMPONENT OF THI! INITIAL

NAMB OF

FUNCTION PHI(X) RI!AL FUNCTION PHI(I,X) IF (I.I!Q.l) PHI= •.. BTC.

X XBND Y(N) BPS HMAX H

INITIAL X-VALUI! FINAL X-VALUB (XBND>X) INITIAL VALUBS FOR Y LOCAL TOLBRANCB MAXIMAL STI!P SIZB INITIAL STBP SIZB GUBSS

OUTPUT PARAMBTBRS

Y(N) SOLUTION AT XI!ND c ---------------------------------------------------------

RBAL*4 Kl(5l),K2(5l),K3(5l),K4(5l),K5(5l),K6(51),K7(51) RBAL*4 Yl(5l),Y(N) LOGICAL RI!JBCT,DISC COMMON/POSITS/IFIRST,LAST,XO,XLAST,IPOS,DISC

C MBANING OF THBSB VARIABLBS: C IFIRST LOWI!ST STI!P NUMBI!R STILL IN MI!MORY COI!F;

451

C LAST ADDRBSS OF LAST DATA WRITTEN BY STORK ON COMMON BLOCK COBF, C MUST Bl! SBT TO 0 IN THE CALLING PROGRAM C BBFORI! THB FIRST CALL. C XO INITIAL POINT, MUST BB SI!T IN THI! CALLING PROGRAM C BBFORB THB FIRST CALL. C XLAST =X+H OF LAST WRITTEN STI!P; C IPOS POSITION OF LAST SUCCESSFUL SBARCH IN FUNCTION YLAGq C DISC LOGICAL VARIABLE, NECESSARY FOR THB DISTINCTION C OF K7 AND Kl OF THB FOLLOWING STBP IN THB CASH C WHEN Y(XO) IS DIFFBRI!NT FROM PHI(XO).

COMMON/STAT/NFCN,NSTI!P,NACCPT,NREJCT C COMMON STAT CONTAINS STATISTICAL INFORMATION: C NFCN NU!oi"BER OF FUNCTION EVALUATIONS C HSTEP NUMBER OF COMPUTED STI!PS C NACCPT NUMBBR OF ACCEPTED STEPS C NREJCT NUMBER OF RBJBCTBD STBPS

COMMON/UROUND/UROUND C UROUND SMALLEST HUMBER SATISFYING l.+UROUHD>l. C (TO BB ADAPTED BY THB USBR)

DATA UROUND/5.8-8/ DATA NMAX/3000/

C NMAX MAXIMAL HUMBBR OF STBPS C INITIAL PREPARATIONS

HMAX=ABS(HMAX) H=AMIHl(AMAXl(l.B-4,ABS(H)),HMAX) B=SIGN(H,l.) BPS=AMAXl(BPS,7.*UROUND) RBJECT=.FALSB. NACCPT=O NREJCT=O NFCN=l NSTEP=O DISC=. T.RUB. CALL FCH(H,X,Y,ll) IF (.NOT.DISC) CALL FCN(N,X,Y,Kl)

C BASIC INTEGRATION STBP 1 DISC=.TRUB.

IF(HSTBP.GT.NMAX.OR.X+.l*H.BQ.X)GOTO 79 IF((X-XEHD)+UROUND.GT.O.) RBTURN IF((X+H-XBHD).GT.O.)H=XBHD-X HSTBP=NSTBP+l

C THB 7 HUNGB-KUTTA STAGBS DO 22 I=l,N

22 Yl(I)=Y(I)+H*.2*Kl(I) CALL FCN(H,X+.2*H,Yl,K2) DO 23 I=l,H

23 Yl(I)=Y(I)+B*((3./40.)*Kl(I)+(9./40.)*K2(I)) CALL FCH(H,X+.3*B,Yl,K3)

Page 20: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

452 Fortran codes

DO 24 I=l,N 24 Yl(I)=Y(I)+H*((44./45.)*Kl(I)-(56./15.)*K2(I)+(32./9.)*K3(I))

CALL FCN(N,X+.8*H,Yl,K4) DO 25 I=l,N

25 Yl(I)=Y(I)+H*((l9372./656l.)*Kl(l)-(25360./2187.)*K2(I) & +(64448./656l.)*K3(I)-(212./729.)*K4(I))

CALL FCN(N,X+(8./9.)*H,Yl,K5) DO 26 I=l,N

26 Yl(I)=Y(I)+H*((9017./3168.)*Kl(I)-(355./33.)*K2(I) & +(46732./5247.)*K3(1)+(49./176.)*K4(I)-(5103./18656.)*K5(I))

XPH=X+H CALL FCN(N,XPH,Yl,K6) DO 27 I=l,N

27 Yl(I)=Y(I)+H*((35./384.)*Kl(I)+(500./lll3.)*K3(I) & +(125./192.)*K4(I)-(2187./6784.)*K5(I)+(ll./84.)*K6(I))

DISC=.TRUE. CALL FCN(N,XPH,Yl,K7) DO 28 I=l,N

28 K2(I)=((71./57600.)*Kl(I)-(71./16695.)*K3(I)+(71./1920.)*K4(I) & -(17253./339200.)*K5(I)+(22./525.)*K6(I)-(l./40.)*K7(I))*H

NFCN=NFCN+6 C ERROR ESTIMATION

ERR=O. DO 41 I=l,N DENOM=AMAXl(l.E-5,ABS(Yl(I)),ABS(Y(I)),2.*UROUND/EPS)

41 RRR=ERR+(K2(I)/DRNOM)**2 ERR=SQRT(ERR/FLOAT(N))

C COMPUTATION OF HNEW C WE REQUIRE .2<=HNEW/H<=l0.

FAC=AMAX1(.l,AMIN1(5.,(ERR/EPS)**(l./5.)/.9)) HNEW=H/FAC IF(ERR.LE.EPS)THEN

C --- STEP IS ACCEPTED NACCPT=NACCPT+1 CALL STORE(X,XPH,Y,N,Kl,K3,K4,K5,K6) DO 44 I=1,N Kl(I)=K7(I)

44 Y(I)=Yl(I) C RECOMPUTE Kl IN THE CASE OF DISCONTINUOUS INITIAL PHASE

IF(.NOT.DISC) CALL FCN(N,XPH,Y,Kl) X=XPH IF(ABS(HNEW).GT.HMAX)HNEW=HMAX IF(REJECT)HNEW=AMIN1(ABS(HNEW),ABS(H)) REJECT=.FALSE.

ELSE C --- STEP IS REJECTED

c ---79

979

c

REJECT=.TRUE. IF(NACCPT.GE.1)NREJCT=NREJCT+l

END IF H=HNEW GOTO 1 FAIL EXIT WRITE(6,979)X FORMAT(' EXIT RETURN END

OF RETARD AT X=',E11.4)

SUBROUTINE STORE(X,XPH,Y,N,FG1,FG3,FG4,FG5,FG6) PARAMETER (NN=4,MXST=800) DIMENSION Y(N),FG1(N),FG3(N),FG4(N),FG5(N),FG6(N) COMMON/COEF/XSTOR(MXST),YSTOR(NN,MXST),

& Cl(NN,MXST),C2(NN,MXST),C3(NN,MXST),C4(NN,MXST) C COEFFICIENTS FOR GLOBAL SOLUTION ARE STORED IN COEF

COMMON/POSITS/IFIRST,LAST,XO,XLAST,IPOS,DISC LAST=LAST+l IFIRST=MAX0(1,LAST-MXST+1) IADR=MOD(LAST-1,MXST)+1 XLAST=XPH XSTOR( IADR) =X DO 2 I=l,NN YSTOR(I,IADR)=Y(I) Cl(I,IADR)=FGl(I)

Page 21: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

c

Retard

C2(I,IADR)=-(l337./4BO.)*FGl(I)+(l05400./27825.)*FG3(I)-& (l35./BO.)*FG4(I)-(54675./212000.)*FG5(I)+(66./70.)*FG6(I)

C3(I,IADR)=(l039./360.)*FGl(I)-(468200./83475.)*FG3(I)+ & (9./2.)*FG4(I)+(400950./31BOOO.)*FG5(I)-(63B./210.)*FG6(I) C4(I,IADR)=-(ll63./ll52.)*FGl(I)+(37900./l6695.)*FG3(I)-

& (415./l92.)*FG4(I)-(674325./50BBOO.)*FG5(I)+(374./l6B.)*FG6(I) 2 CONTINUE

RETURN END

REAL FUNCTION YLAG(I,X,PHI) PARAMETER (NN=4,MXST=BOO) LOGICAL DISC COMMON/COEF/XSTOR(MXST),YSTOR(NN,MXST),

& Cl(NN,MXST),C2(NN,MXST),C3(NN,MXST),C4(NN,MXST) COMMON/POSITS/IFIRST,LAST,XO,XLAST,IPOS,DISC COMMON/UROUND/UROUND

C --- INITIAL PHASE IF (DISC) THEN

IF(ABS(X-XO).LE.(3.*UROUND*ABS(X)))DISC=.FALSE. IF(X.LE.XO)THEN

YLAG=PHI(I,X) RETURN

END IF END IF

C --- COMPUTE THE POSITION OF X IF (X.LT.XSTOR(IFIRST)) THEN

WRITE (6,*) ' MEMORY FULL, MXST ',MXST STOP

END IF IPOS=MAXO(IFIRST,MINO(LAST,IPOS)) IADR=MOD(IPOS-l,MXST)+l IF (X.LT.XST.OR(IADR) .AND. IPOS.GT. !FIRST) THEN

IPOS=IPOS-1 GOTO l

END IF 2 IADR=MOD(IPOS,MXST)+l

IF (IPOS.LT.LAST) THEN IF (X.GT.XSTOR(IADR)) THEN

IPOS=IPOS+l GOTO 2

END IF END IF

C --- COMPUTE THE DESIRED APPROXIMATION IADR=MOD(IPOS-l,MXST)+l IF (IPOS.EQ.LAST) THEN

H=XLAST-XSTOR(IADR) ELSE

H=XSTOR(MOD(IPOS,MXST)+l)-XSTOR(IADR) I!ND IF S=(X-XSTOR(IADR))/H YLAG=YSTOR(I,IPOS)+H*S*(Cl(I,IPOS)+S*(C2(I,IPOS)

& +S*(C3(I,IPOS)+S*C4(I,IPOS)))) RETURN I!ND

453

Page 22: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Bibliography

N.H. Abel (1826): Untersuchungen Uber die Reihe:

l+ .!!L + m(m-1) 2+ m(m-l)(m-2)x3+ usw 1 X 1·2 X 1•2·3 ........ .

Crelle J. f. d. r. u. angew. Math. (in zwanglosen Heften), vol.1, p.311-339.

N.H. Abel (1827): Ueber einige bestimmte lnlegra/1!, Crelle J. f. d. r. u. angew. Math., vol.2, p.22-30.

M. Abramowitz and IAStegun (1964): Handbook of mathematical functions, Dover, 1000 pages.

J.C. Adams (1883): see F.Bashforth (1883). A.C. Aitken (1932): On interpolation by itemtion of proportional parts, without the

~ of dilferences; Proc. Edinburgh Math. Soc. Second ser. Vol.3, p.56-76.

J. Albrecht (1955): BeitriJge zum Runge-KuttiJ-Verfahren, ZAMM, vol.35, p.100-110.

V.M. Alekseev (1961): An estimate for the perturbations of the solution of ordinary dilferenlial equations (Russian). Vestn. Mosk. Univ., Serl, Math. Meh, 2, p.28-36.

JJe Rood d' Alembert (1748): Suite des recherches sur II! aJlcul intigml, quatileme paTtie: Methodes pour in.tigrer quelques equations dilferentiel/es, Hist. Acad. Berlin, TomJV, p.275-291.

R.F. Arenstorf (1963): Periodic solutions of the restrkted tlwe body problem repre­senting (llllllytic continuations of K eplerian elliptic motions, .Amer. J. Math., vol.LXXXV, p.27-35.

C. ArzelJi (1895): Sul/e funzioni di linee, Memorie dell. R. Accad. delle Sc. di Jb. logna, 5e aerie, vol.V, p.225-244, see also: vol.V, p.257-270, vol.VI, (1896), p.131-140.

N. Bakhvalov (1976): Methodes numhiques, Editions Mir, Moscou 600Jl>., russian edition 1973.

F. Bashforth (1883): An attempt to test the theories of copilklry action by comparing the theoretical and measured forms of drops of fluid. With an explanation of the method of integration employed in constructing the tabli!s which give the theoreticalfonn of such drops, by J.C.Adams, Cambridge Univ. Press.

R.H. Battin (1976): Resolution of Runge-Kutta-NystTDm condition equations through eighth order, AIAAJ., vol.14, p.1012-1021.

F.L. Bauer, H. Rutishauser and E. Stiefel (1963): New aspects in numerical quadm­tlm!. Proc. of Symposia in Appl. Math. vol.15, p.199-218, Am. Math. Soc.

PA Beentjes and WJ. Gerritsen (1976): Higher order Runge-Kutta methods for the numerical solution of second order dilferenlial equations without first deriva­tives, Report NW 34/76, Math. Centrum, Amsterdam ..

Page 23: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

456 Bibliography

H. Behnke and F. Sommer (1962): Theorie der ant~lytiacJum Frurktionen einer kom­plexen VeriiiiMrlichen. Zweite Auflage. Springer Verlag, BerHn­Gottingen-Heidelberg.

A. Bellen (1984): One-step collotxltion for delay dilfermtial equations, J. Comput. Appl. Math. Vol. 10, p275-283.

R. Bellman and K.L. Cooke (1963): Dfllerential-Dfllemu:e equations, Academic Press, 462pp.

I. Bendixson (1893): Sur le calcul des intigrales d'rm sysfeme d'equations dif­ferentie/Jes par des approximations successivn, Stock. Akad. Forb., Vol.51, p.599-612.

I. Bendixson (1901): Sw les courlJes difinies par des equations dfllmn.tielles, Ada Mathematica, vol24, p.1-88.

Jac. Bernoulli (1695): Explicaliones, Annotationes cl: Addiliones od ea, quae in Actis sup. anni de Curva Elastica, lsochrona ParacmtTicil, cl: Veloria, hinc inde memorota, cl: partim contTr:IVersa legr.uuliU'; ubi de Linea mediarum directio­IUUn, a/lisp novis, Ada Erudit. Lipsiae, Anno MDCXCV, p. 537-553.

Jac. Bernoulli (1697): Solutio Problematum Fratemorum, Pecalitlri Programmate Cal. Jan. 1697 Groningae, nee non Actorum Lips. mense Jrm. cl: Dec. 1696, cl: Febr. 1697 proposilorum: rma cum Propositione reciproco aliorum. Ada Erud. Lips. MDCXCVII, p211-217.

Job. Bernoulli (1696): Problema novum Mathematici8 proposilorum. Acta Erud. Lips. MDCXCVI, p269, ~ra Omnia vol.I, p.161 and 165, Lausannae & Genevae 1742.

Job. Bernoulli (1697): De Conoidibus et Sphaeroidibus quaedom. Solutio analytiaJ Aequationis in Actis A. 1695, pag. 553 proposilae, Ada E'.rud. Lip;., MDCXCVII, p.113-118.

Job. Bernoulli (1697b): Solutioque Problematis a se in Actis 1696, p.269, proposil, de inveniendo Linea Bmchystochrona, Acta E'.rud.Lips. MDCXCVII, p.206, ~ra Omnia vol.I, p.187-193.

D. Bernoulli (1760): ES811i d'rme IIOIWelle analyse de Ia mortali/e causee par Ia petite wrote, et des avantages de I' inoculation pour lo ptivenir, Hist. et M~. de l'.Acad. Roy. Sciences Paris, 1760, p.1-45; Werke Band 2, p235-267.

L. Bieberbach (1923): Theorie der Dfllerentialgleicluu&gen, Grundlebren Bd.VI, Springer Verlag.

L. Bieberbach (1951): On the remainder of the R unge-K utta fonnulo in the theory of ordinary differential equations, Zeitschr. angew. Math.Pbys. (ZAMP), vo12, p233-248.

G. Birkhoff and R.S. Varga (1965): Discretization errors for weU-set Cauchy prob­lems I, Journal of Math. and Physics, vol.XLIV, p.1-23.

C. de Boor and B. Swartz (1973): Col/octJtion at Gaussian points, SIAM J. Numer. Anal., vol.lO, p.582-606.

R. Bu1irsch and J. Stoer (1964): FelalerobschlJtzungen und Extropolotion mil mtio­nalen Frurktionen bei Verfahren wnn Richardson-Typus, Num. Math. Vol.6, p.413-427.

R. Bulirsch and J. Stoer (1966): Numerical treotment of ordinary differential equa­tions by extrapolotion methods, Num. Math. vol.8, p.1-13.

K. Burrage (1985): Order and stability propett~s of explicit mtdtivable metltotb. Appl. Numer. Anal., vol.l, pp.363-379.

Page 24: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Bibliography 457

K. Burrage and J.C. Butcher (1980): Non-linear stability of a general closs of differentkll equation methods. BIT, vol.20, pp.l85-203.

K. Burrage and P. Moss (1980): Simplifying assumptions for the order of partitioned multivalue methods. BIT, vol.20, w.452-465.

J.C. Butcher (1963): Coefficients for the study of Run.ge-Kutta integration processes, J. Austral. Math. Soc., vol.3, p.l85-201.

J.C. Butcher (1963a): On the integration process of A. Huta, J. Austral. Math. Soc., vo1.3, p.202-206.

J.C. Butcher (1964a): ImpliciJ Run.ge-Kutta Processes, Math. Comput. vol.l8, p50-64.

J.C. Butcher (1964b): On Runge-Kutta processes of high order, J.Austral. Math. Soc. vol.IV, Part2, p.179-194.

J.C. Butcher (1964c): Integration processes based on Radau quadrature formulas, Math. Comput., Vol.18, p233-244.

J.C. Butcher (1965a): A modified mu/Jistep method for the numerical integration of ordinary differen.tkll equations. J. ACM, vol.l2, pp.124-135.

J.C. Butcher (1965b): On the attainable order of Run.ge-Kutta methods, Math. of Comp. vol.19, p.408-417.

J .C. Butcher (1966): On the convergence of numerical solutions to ordinary differential equations, Math. Comput., vol.20, p.l-10.

J.C. Butcher (1967): A mu/Jistep generalization of Runge-Kutta methods wiJhfour or jive stages. J. ACM, vol.l4, p.84-99.

J.C. Butcher (1969): The effective order of Run.ge-Kutta methods, in: Conference on the numerical solution of differential equations, Lecture notes in Math. Vol.109, p.133-139.

J.C. Butcher (1972): An algebraic theory of integration methods, Math. Comput. Vol.26, p.79-106.

J.C. Butcher (1975): An order bound for Run.ge-Kutta methods, SIAM J.Num. Anal. vol.12, p.304-315.

J.C. Butcher (1981): A generalization of singly-implicit methods, Bff, vol21, p.175-189.

J.C. Butcher (1984): An application of the Run.ge-Kutta space, BIT, vol24, p.425-440.

J.C. Butcher (1985a): General linear method: a survey, Appl. Num. Math., vol.l, p273-284.

J.C. Butcher (1985b): The non-existence of ten stage eighth order explicit Run.ge­Kutta methods, BIT, vol25, p521-540.

G.D. Byrne and A.C. Hindmarsh (1975): A polyalgorithmfor the numerical solution of ordinary differential equations, ACM Trans. on Math. Software, vol.l, No.1, p.71-96.

G.D. Byrne and RJ. Lambert (1966): Pseudo-Run.ge-Kutta methods involving two points, J. Assoc. Comput. Mach., vol.13, p.114-123.

A.L. Cauchy (1824): Resume des L~on.s donnees a l'Ecole Royale Polyteclan.iqul!. Suite du Cak:ul Injinuesimal,· published: Equations difftrentielles ordi­naires, ed. Chr. Gilain, Johnson 1981.

A.L. Cauchy (1831): Sur Ill mecan.ique celeste et sur un. nouveau calcul. appete a.Jk:ul des limites, 1u a l'acad. de Turin le 11 oct 1831; also: exerc. d'anal. et de pysique math, 2, Paris 1841; oeuvres (2), 12.

Page 25: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

458 Bibliography

AL. Cauchy (1839-42): Several articles in Comptes Rendus de tAcod. des Sciences de Paris. (Aug. 5, Nov. 21, 1839, June 29, O:t. 26, 1840, etc).

A Cayley (1858): A memoir on the theory of matrices, Phil. Trans. of Royal Soc. of London, vol.CXLVlll, p.17-37, Mathematical Papers vol2, Nr.152, p.475.

F. Ceschino and J. Kuntzmann (1963): Probll!mes differentiels de c0Niilio118 iniliales (metlwdes numeriques), Dunod Paris, 372pp.

F. Ceschino and J. Kuntzmann (1963): Probll!mes dilfh'entiel.s de condilions iniliales, Dunod Paris; english translation: Numerical solutions of initial value problems, Prentice Hall1966

F. Ceschino (1961): Modification de Ia longueur du pas dollS !integration numerique par les methodes a paslles, Chiffres 2, p.101-106.

F. Ceschino (1962): Evaluation de terreur par pas dollS les probll!mes differentiels, Chiffres vol.5, p.223-229.

AC. Clairaut (1734): Sollllion de pluaieurs probfemes ou il s'agit de trouver des COIU'bes dont Ia propr{ete COIISisle dollS une certaine relation entre leurs branches, exprintee par une EqiUltion donnee, M~moires de Math. et de Phys. de 1' Acad. Royale des Sciences, Paris, Annoo MDCCXXXIV, p.196-215.

L. CoDatz (1951): Numerische Behandltuag von DUferentiolgleidumgen, Grundlehren Band LX, Springer Verlag, 458pp; second edition 1955; third edition and english translation 1960.

P. Collet and J.P. Eckmann (1980): Iterr:rted maps on the interval as dynamical sys­tems, Birkhluser, 248pp.

GJ. Cooper and J.H. Verner (1972): Some explicit R~~~&ge-Kutta methods of 1tJgh order, SIAM J.Numer. Anal. vol.9, p.389-405.

GJ. Cooper (1978): The order of COI&l'ergence of general linear method8 for ordinllry differential eqaations. SIAM, J. Numer. Anal., vol.15, pp.643-661.

S.A. Corey (1906): A method of approximation, Amer. Math. Monthly Vol.13, p.137-140.

P.H CoweD and A.C.D. Crommelin (1910): Investigation of the motion of Halley's comet from 1759 to 1910. Appendix to Greenwich Cblervations for 1909, Edinburgh, p.1-84.

D.M. Creedon and JJ.H. Miller (1975): The stability propertil!s of q-step backward­dijference sdaemes, BIT, vol.15, p244-249.

M. Crouzeix (1975): Sur !approximation des hpultio118 diffirentielles operr:rtionnelles /illklires par des mitlrodes de Rllllge-Kutta, Th~e d'6tat, Univ. Paris 6, 192pp.

M. Crouzeix and F.J. Usbona (1984): The convergence ofvariiJble-stepsize, variiJble fomrllkl, mu.llistep methods, SIAM J. Num. Anal. 21, p.512-534.

C.W. Cryer ( 1971): A proof of the instability of backward-difference multistep methods for the numerical integration of ordinary differential eqiUltions, Tech. Rep. No.117, Comp. Sci. Dept., Univ. of WJSconsin, p.1-52.

C.W. Cryer (1972): On the instability of high order backward-difference multistep method8, BIT, vol.12, p.17-25.

W J. Cunningham (1954): A nonlinear differentiol-dUference eqiUltion of growth, Proc. Mat. Acad. Sci., USA, vol.40, p.708-713.

AR. Curtis (1970): An eighth order R 1111ge-KU#Q process with eleven ftmc1ion evalu.a­tions per step, Numer. Math. Vol.16, p268-277.

Page 26: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Bibliography 459

AR. Curtis (1975): High-order explicit Runge-Kuttll formukle, their uses, and limita­tions, JJnst. Maths Applies, vol.16, p.35-55.

C.F. Curtiss and J.O. Hirschfelder (1952): Integration of stiff eqlUllions. Proc. of the National Academy of Sciences of U.S., vol.38, p.235-243.

G. Dahlquist and R. Jeltsch (1979): Genemlized dislcs of contraelivity for explicit and implidt Rrmge-Kutta methods. Report TRITA-NA-7906, NADA, Roy. lnst. Techn. Stockholm.

G. Dahlquist (1956): Convergence and stability in the numeriall integration of ordi­nary dflferential eqiUllions, Math. Scand., vol.4, p.33-53.

G. Dahlquist (1959): Stability and error bounds in the numerical integration of ordi­nary differential eqlUllions, Trans. of the Royal Inst. of Techn., Stock­ho1m, Sweden, Nr.130, 87pp.

G. Dahlquist (1985): 33 years of numericol instability, part.I, BlT, vol.25, p.188-204.

J. Descloux (1963): A note on a paper by A. Nordsiedc, Report No.131, Dept. of Comp. Sci., Univ. of Dlinois at Urbana-Champaign.

P. Deuflhard and E. Hairer ed. (1983): Numerical treatment of inverse problems in dflferential and integral eqlUllions, Birkhauser, Boston, Basel, 357pp.

P. Deuflhard and G. Bader (1982): Multiple shooting techniques revisited, Preprint Nr.163, Univ. Heidelberg, Inst. Angew. Math., D-6900 Heidelberg 1. Summary published in: P. Deu:flhard, E. Hairer, (1983) p.74-94.

P. Deuflhard (1980): Recent advances in mullii* shooting techniques; In: Computa­tional techniques for ordinary differential equations (GladweD-Sayers, ed.), Section 10, p.217-272, Academic Press.

P. Deuflhard (1983): Order and stepsize control in extrapolation methods, Num. Math. vol.41, p.399-422.

P. Deu:flhard (1985): Recent progress in extrapolation methods for ordinary differen­tial eqlUltions, SIAM Rev., vol.27, w.505-535.

J. Donelson and E. Hansen (1971): Cyclic composite multistep prediclor-com!clor methods. SIAM, J. Numer. Anal., vol.S, pp.137-157.

J.R. Dormand and PJ. Prince (1978): New Runge-Kuttll algorithms for numerical simulation in dynamical astronomy, Celestial Mechanics, vol.18, p.223-232.

J.R. Dormand and PJ. Prince (1980): A family of embedded Rrmge-Kuttaformulae, J.Omtp . .Appl. Math. vol.6, p.19-26.

R.D. Driver (1977): Ordinary and delay dflferentilll eqlUltions, Applied Math. Sci­ences 20, Springer Verlag, 501pp.

B.L. Ehle (1968): High order A-stable methods for the numerical solution of systems of D.E.'s, BlT vol.8, p.276-278.

N.F. Eispack (1974): B.T.Smith, J.M. Boyle, B.S.Garbow, Y .Jkebe, V.C.Kiema, C.B.Moler: Matrix Eigensystem Routines, (Fortran-translations of algo­rithms published in Reinsch and Willdnson), Lecture Notes in Com­puter Science, vol.6, Springer Verlag.

H. Eltermann (1955): FehlembschiJtzung bei 11/Jherungsweiser LDsrmg von Systemen von Differelllialgleichungen erster Ordnung, Math. Zeitschr. vol.62, p.469-501.

R. England (1969): Error estimates for Runge-Kutta type solutions to systems of ordi­nary dflferential eqlUllions; The Computer J. vol.12, p.166-170.

Page 27: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

460 Bibliography

W.H. Enright, T.E. Hull and B. Undberg (1975): Comparing numerical methods for stiff systems ofOD.E.s, BIT vol.15, p.l0-48.

W.H. Enright, K.R. Jackson, S.P. Norsett and P.G. Thomson (1985): InJerpolanls forRunge-Kuttaformulos, Technical Report 180/85, Dept. Comput. Sci­ence, Toronto, Canada M5S lAS, 36 pp.

L. Euler (1728): Nova methodus innumerabill!s aequationes dijfenmtioles ~cundi gradus reducendi ad aequationes differenliales primi gradus, Comm. acad. scient. Petrop. vol.3, p.124-137; Q:lera Onnia vol.xxn, p.l-14.

L. Euler (1743): De integratione aequationum differenlialium altion.un graduum, Mis­celJanea Berolinensia vol.7, p.193-242; Opera Onnia vol.XXU, p.lOS-149. See also: Letter from Euler to Job. Bernoulli, 15Sept.1739.

L. Euler (1744): Methodus inveniendi lineos CUIWlS mttXimi minimive proprietate gau­dmtes .. , Lausannae & Genevae, Opera Onnia (intr. by Caratheodory) vol.xxiV, p.l-308.

L. Euler (1750): Methodus aequationes dUferentioles altiorum graduum integrandi ulterilu promota, Novi Comment. acad. scient. Petrop. vol.3, p.3-35; Q:lera Omnia vol.xxn, p.181-213.

L. Euler (1756): Elementa calculi variationum, presented September 16, 1756 at the .Acad. of Science, Berlin; printed 1766, Q:lera Omnia vol.XXV,p.141-176.

L. Euler (1768): Instilutionum Calculi Integra/is, Volumen Primum, Opera Omnia volJO.

L. Euler (1769): Institutionum Calculi Integra/is, Volumen Secundum, Opera Onnia voDrn.

L. Euler (1n8): Specimen transformationis singu/aris serienum, Nova acta. acad. Petrop., vol.12 (1794), p.58-70, Q:lera Onnia vol.xvi, p.41-55.

E. Fehlberg (1958): Eine Methode zur Fehlerverl.:leinenmg beim Runge-Kutta­Verfahren, ZAMM vol.38, p.421-426.

E. Fehlberg (1964): New high-order Runge-Kutta formulas with step size control for systems of first and second ortkr differential ~uations, ZAMM, vol.44, Sonderheft 117-119.

E. Fehlberg (1968): Clossical fifth-, sixth-, seventh-, and eighth ortkr Runge-Kutta formulos wish step size conJrol; NASA Technical Report 287 (1968); extract published in Computing vol.4, p.93-106 (1969).

E. Fehlberg (1969): Low-ortkr classical Runge-Kutta formulos with step size control and their application to some heat transfer problems, NASA Technical Report 315 (1969), extract published in Computing vol.6, p.61-71 (1970).

E. Feh1berg (1972): Classical eighth- and lower-ortkr Runge-Kutta-NystriJm formulos with stepsize control for special second-order dUferential equations, NASA Technical Report R-381.

M. Feigenbaum (1978): Quantitative universality for a closs of nonlinear transforma­tions, J.Stat. Phys. vol.19, p.25-52, vol21 (1979), p.669-706.

J.R. Field and R.M. Noyes (1974): Oscillations in chemical systems. IV. Limit cycle behavior in a model of a reol chemical reaction, J. Chem. Physics, vol.60, p.1877-1884.

S. Filippi and J. Graf (1986): New Runge-Kutta-NystrDm formulo-pairs of ortkr 8(7), 9(8), 10(9) and 11(10) for differential equations of the form y "=! (x ,y), J. Comput. and Applied Math., vol.14, p.361-370.

Page 28: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Bibliography 461

R. Fletcher and D.C. Sorensen (1983): An algorithmic derivation of the Jordtm canonicalfonn, Amer. Math. Monthly, vol.90, No.1, p.12-16.

C.V.D. Farrington (1961-62): Ex~lt8iona of the predictor-con-ector method for the solution of sys~s of ordinory dilferen.tiol equatlons, Comput. J. 4, p.8Q. 84.

J.B.J. Fourier (1807): Sur Ill propagation de Ill chDieur, unpubHshed manuscript; pubHshed: La thoorie analytique de Ia chaleur, Paris 1822.

V. Franceschini (1980): Feigenbaum sequence of bifurcatioM in the Lorrmz model, J.Stat, Phys. vol.22, p.397-406.

R.A. Frazer, W .P. Jones and S.W. Skan (1937): Approximations to fu.nctWns and to the solutioM of differen.tiol equations, Reports and Memoranda Nr.1799 (2913), Aeronautical Research Committee. 33pp.

A. Fricke (1949): Ueber die Feh/erabscltlJtZilllg des Adtunsschen Vetfahre118 ZIU' 1~­gration gewDhnlicher Dilferentilllg~ichungen ertter Ordnung, ZAMM, vol.29, p.165-178.

M. Frommer (1934).: Ueber dtu Auftreten von Witbeln ruul StrUdeln (geschlosstmer ll1ld spiraliger lntegrallcurven) inder Umgebung rationa~r Unbestimmtlaeits­s~l/en, Math. Ann., vol.109, p.395-424.

L. Fuchs (1866): Zur Theoril! der linearen Dijferentiolgleichungen mit veriJnderlit:Mn Coejficienten, Crelle J. f. d. r. u. angew. Math., vo1.66, p.121-160 (prepubHshed in "Programm der stadtischen Gewerbeschule zu Berlin, Oltem 1865'~.

P. Funk (1962): VariotioMrechtumg ruul ihre Anwendluag in Physilc ruul Technilc, Springer Verlag, Grundlehren Bd. 94, 676 p.

C.F. Gauss (1812): Disquisitiones genera~s circa seriem injinitam

l +~X + u(u+1)S(p+1) XX

1"'Y 1 . 2 . 'Y('Y+1)

+ u(u+1)(u+2)p(J!+l)(p+2) 3 + 1 x e c, 1. 2. 3. 'Yb+1)(,+2)

Werke vol.3, p.123-162.

W. Gautschi (1962): On inverses of V andermonde and confluent Vandennonde matri­ces, Numer. Math. vol.4, p.117-123.

C.W. Gear and D.S. Watanabe (1974): Stability and convergence of variable order multis~p methods, SIAM J. Num. Anal. 11, p.1044-1058.

C.W. Gear and K.W. Tu (1974): TM effect of variable mesh size on the stability of multistep methods, SIAM J. Num. Anal. 11, p.1025-1043.

C.W. Gear (1965): Hybrid methods for initial value problems in ordinory differential equatioM. SIAM J. Numer. Anal., ser.B, vol.2, p.69-86.

C.W. Gear (1971): Numerical initial value problems in ordinary differential equatio118, Prentice-Ha11, 253pp.

A. Gibbons (1960): A program for the automatic in.tegmtion of diJferentiol equations using the method of Taylor series, Computer J. vol.3, p.lOS-111.

S. Gill (1951): A process for the step-by-step integration of dilferentkll equatio118 in an automatic digillll computing machine, Proc. Cambridge Philos. Soc., vol.47, p.95-108.

B. Giovannini, L. Weiss-Parmeggiani and B.T. Ulrich (1978): Phase lot:ting in coupled Josephson weak links, Helvet. Physica Acta, vol51, p.69-74.

Page 29: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

462 Bibliography

H.H. Goldstine (1980): A History of the Calculus of Variations, Springer Verlag, 410p.

G.H. Golub and J.H. Wilkinson (1976): IU.-condiJioned eigensystems and the compu­tation oftheJordon canonicolfonn, SIAM Review, vol.18, p.578-619.

B.A Gottwald (1985): Zur Modellierung zeitverzDgerter biologischer Prozesse, lnfor­matik Fachberichte, vol.109, p.350-354, Springer Verlag.

W .B. Gragg and H.J. Stetter (1964): Generalized multistep predictor-corrector methods. J. ACM, vol.ll, pp.188-209.

W.B. Gragg (1964): Repeated extrapolation to the limiJ in the numericol solution of ordinary differential equations, Thesis, Univ. of California; see also SIAM J. Numer. Anal., vol2, p.384-403 (1965).

W.B. Gragg (1965): On extrapolation algorithms for ordinary initial value problems, SIAM J. Num. Anal., ser.B, vol2, p.384-403.

R.D. Grigorieff (1977): Numerik gewi>hnlicher Differentiolgleichungen 2. Teubner Studienbtlcher, Stuttgart.

R.D. Grigorieff (1983): Stability of multistep-methods on variable grids, Numer. Math. 42, p.359-377.

W. Grobner (1960): Die Liereihen und ihre Anwendungen, D. Veri. d. Wiss. Bertin, 2nd ed. 1967.

T.H. Gronwall (1919): Note on the derivatives with respect to a parameter of the solu-tions of a system of differential equations, Ann. Math. vol.20, p.292-296.

H. Hahn (1921): Theorie der reel/en Funlctionen, Springer Verlag Bertin, 600pp. W. Hahn (1967): Stability of motion, Springer Verlag, 446pp. E. Hairer and G. Wanner (1973): Mukistep-multistage-multiderivative methods for

ordinary differential equations, Computing Vol.ll, p287-303. E. Hairer and G. Wanner (1974): On the BUICher group and general multi-value

methods, Computing Vol.13, p.l-15. E. Hairer and G. Wanner (1976): A theory for Nystrr»n methods, Numer. Math.,

vo125, p.383-400. E. Hairer and G. Wanner (1983): On the instability of the BDF fonnulas, SIAM J.

Numer. Anal., vol.20, No.6, p.1206-1209. E. Hairer and 01. Lubich (1984): Asymptotic expansions of the global error of

fixed-stepsize methods, Numer. Math. vol.45, p.345-360. E. Hairer (1977): Methodes de NystriJm pour !equation differentiel/e y "=/ (x ,y ),

Numer. Math., vol27, p283-300. E. Hairer (1978): A Runge-Kutta method of order 10, J.Inst. Maths AppHcs, vol.21,

p.47-59. E. Hairer (1981): Order conditions for numerical methods for partitioned ordinary

differential equations, Numer. Math., vol.36, p.431-445. E. Hairer (1982): A one-step method of order 10 for y "=! (x ,y ), IMA J. Num.

Anal. vol2, p.83-94. P.C. Hammer and J.W. Hollingsworth (1955): Trapezoidal methods of approximat­

ing solutions of differential equations, MTAC vol.9, p.92-96. N.D. Hayes (1950): Roots of the transzendental equation associated with a certain

difference-differential equation, J. of London Math. Soc., vol25, p226-232.

Page 30: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Bibliography 463

H.M. Hebsacker (1982): Conditions for the coefficients of Runge-Kutta methods for systems of n -th order differential equations, J. Comput. Appl. Math., vol.8, p.3-14.

P. Henrici (1962): Discrete variable methods in ordinary differentio.l equations. John Wiley & Sons, Inc., New-York-London-Sydney.

P. Henrici (1974): A~d and computational complex analysis, Volume 1, John Wiley & Sons, New York, 682pp.

Ch. Hermite (1878): Extrait d'une lettre de M. Ch. Hermite a M. Borchardt sur Ia formule d'interpolation de Lagrange, J. de Crelle, vol.84, p.70; Oeuvres, tome m, p.432-443.

K. Heun (1900): Neue Methode zur approximativen Integration der Differentio.l­gkichungen einer unabhiJngigen VeriJnderlichen, Zeitschr. fOr Math. u. Phys., vol.45, p23-38.

A. C. Hindmarsh (1972): GEAR: ordinary differentio.l equation system solver, UCID-30001, Rev .2, LLL, Livermore, Calif.

A.C. Hindmarsh {1980): LSODE and LSODI, two new initio./ value ordinary differ­entilll equation solvers, ACM Signum Newsletter 15,4.

M.W. Hirsch and S. Smale {1974): Differentio.l equations, dynamicol systems and linear algebra, Acad. Press, 358pp.

E.W. Hobson (1921): The theory of functions of a real varUJ.ble, vol.I, Cambridge, 670pp.

G.'t Hooft (1974): Magnetic monopoles in unified gauge theories, Nucl. Phys. vol.B79, p276-284.

E. Hopf (1942): Abzweigung einer periodischen LtJsung 11011 einer stationllren LDsung eines Differentia/systems, Ber. math. physik. Kl. Akad. d. Wiss. Leipzig, Bd.XCIV, p.3-22.

M.K. Horn (1983): Fourth and .fifth-order scoled Runge-Kutta algorithms for trt!ating dense output, SIAM JNumer. Anal. vol20, p558-568.

P J.van der Houwen (1977): Construction of integration formulas for initio./ value problems, North-Holland Amsterdam, 269pp.

T.E. Hull, W.H. &right, B.M. Fellen and A.E. Sedgwick (1972): Comparing numerical methods for ordinary differential equations, SIAM J. Numer. Anal., vol.9, p.603-637.

T.E. Hull and R.L. Johnston (1964): Optimum Runge-Kutta methods, Math. Com­put., vol.18, p.306-310.

T.E. Hull (1967): A search for optimum methods for the numerical integration of ordinary differential equations, SIAM Rev., vol.9, p.647-654.

B.L. Hulme (1972): One-step piecewise polynomio.l Galerlcin methods for initio.l value problems, Math. of Comput. vol26, p.415-426.

W.R Hundsdorfer and MN. Spijker (1981): A note on B-stability of Runge-Kutta methods, Num. Math. Vol.36, p.319-331.

A. Hurwitz (1895): Ueber die Bedingungen, unter welchen eine Gleichung nur Wur­zeln mit negativen reeUen Theilen besitzt, Math. Ann., vol.46, p273-284; Werke vol2, p533ff.

E.L. lnce (1944): Ordinary differentilll equations, Dover Publications, New York, 558 pp.

G. Iooss and DD. Joseph (1980): Elementary stability and bifurcotion theory, Springer VerJag, 286 pp. (see chapter Vll).

Page 31: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

464 Bibliography

C.GJ. Jaoobi (1845): Theorio novi multiplicatoris systemati aequationum differen.­tialum vulgarium applicandi, Crelle J. f. d. r. u. angew. Math, vol.29, p.213-279, 333-376.

C. Jordan (1870): Traite ihs Substitutions et ihs eqllQtions algihriques, Paris 667pp. C. Jordan (1928): Sur un.e formule d'interpolation., Atti Congresso Bologna, vol 6,

p.157-177 B. Kaogstrom and A. Rube (1980): An. algorithm for numerical computation. of the

Jordan normal form of a complex matrix; ACM Trans. Math. Software, vol.6, p.398-419. (Received May 1975, revised Aug. 1977, accepted May 1979).

S. Kakutani and L. Marcus (1958): On. the non-linear difference-differential eqllQtion. y'(t)=[A -By(t--r)]y(t), in: Contributions to the theory of non­linear oscillations, Ed. by S.Lefschetz, Princeton, vol.IV, p.l-18.

E. Kamke (1930): Ueber die ein.deutige Bestimmtheil ihr In.tegrale von. Differen.tiol­gleichugn.en. II, Sitz. Ber. Heidelberg Akad. Wiss. Math. Naturw. Kl., 17. Abhandl., see also Math.Zeitschr., vol. 32, p.l01-107.

E. Kamke (1942): Differen.tialgleichun.gen, LDsun.gsmethoden und LDsungen., Becker & Erler, Leipzig, 642pp.

K.H. Kastlunger and G. Wanner (1972): Runge Kutta processes with multiple n.oihs, Computing vol9, p9-24.

K.H. Kastlunger and G. Wanner (1972b): On. Turon type implicit Runge-Kutta methods, Computing vol.9, p.317-325.

H.B. Keller (1968): Numericol methods for two-point boundary-value problems, Blais­dell Publ. Comp., 184 pp. (see section 2.4).

W.O. Kermack and A.G.Mc. Kendrick (1927): Contributions to the mathematical theory of epidemics (Part I), Proc. Roy. Soc., A, vol.115, p.700-721.

R. King (1966): Runge-Kutta methods with constrained minimum error bounds, Math. Comput., vol.20, p.386-391.

H. Knapp and G. Wanner (1969): LIESE II, A program for ordinory differential eqllQtion.s using Lie-series, MRC Report No.l008, Math. Research Center, Univ. Wisconsin, Madison, Wise. 53706.

G. Kowalewski (1908): see Leibniz (1693). F.T. Krogh (1969): A variable step variable order multistep method for the numerical

solution of ordinary differential eqllQtion.s, Information Processing 68, North-Holland, Amsterdam, p.l94-199.

F.T. Krogh (1973): Algorithms for changing the step ~·ize, SIAM J. Num. Anal. 10, p.949-965.

F.T. Krogh (1974): Changing step size in. the integration. of differential eqllQtion.s using modified ihvided differences, Proceedings of the Conference on the Num. Sol. of ODE, Lecture Notes in Math. No.362, Springer Verlag New York, p.22-71.

N. Kryloff and N. Bogoliuboff (1947): IntTrJduction. to non-linear Mechanics, free translation by S. Lefschetz, Princeton Univ. Press, 105pp.

E.E. Kummer (1839): Note sur tin.tegrotion ih !equation. d"yldx" =xmy par ihs integrates dejinies, Crelle J. f. d. r" u. angew. Math., vol.19, p.286-288.

J. Kuntzmann (1961): Neuere En.twickebmgen. der Methoih von. Run.ge-Kutta, ZAMM, vol.41, p.28-31.

J. Kuntzmann (1959): Deux formules optimales du type ih Run.ge-Kutta, Chiffres, vol.2, p.21-26.

Page 32: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Bibliography 465

W. Kutta (1901): Beitrag zur nJJherungsweisen Integration totaler Dif!erentitll­gleichungen, Zeitschr. ftlr Math. u. Phys., vol.46, p.435·453.

J.L.de Lagrange (1759): Recherches sur /Q 1Ullu~ et /Q propagation duson, Miscell. Taurinensia t.l, Oeuvres t.1, p39-148.

J.L.de Lagrange (1762): Solution de dif!erents problemes de Calcullntegral, Miscell. Taurinensa, t.m, Oeuvres t.1, p.471-668.

J.L.de Lagrange (1774): Surles Integrates particufre~s des Equations dgfe~ntielles, Oeuvres, tom.4, p5-108.

J.L.de Lagrange (1775): Recherche sur les Suites Recurrentes, Nouveaux Mem. de 1' Acad. royale des Sciences et Belles-Lettres, Berlin. Oeuvres vol.4, p.159.

J.L.de Lagrange (1788): Mecanique analytique, Paris, Oeuvres t.ll et 12. J .L.de Lagrange ( 1792): M hnoire sur f ex~ssion du terme general des serres

recurrentes, lorsque !equation geniratrice a des racines egales, Nouv. Mem. de 1' Acad. royale des Sciences de Berlin, Oeuvres t5, p.627-641.

J.L.de Lagrange (1797): Theorie des fonctions analytiques, contenant les principes du calcul differentiel, digages de toute consideration d'infiniment petits, d'evanouissants, de limites et de fluxions, et riduits a !analyse algebrique des quantites.finies, Paris, 1797, nouv. ed. 1813, Oeuvres Tome 9.

P .S. Laplace (An Xlli = 1805): Supplhnent au dixleme livre du Traiti de mecanique celeste sur l' action a.rpillaire, Paris chez Courcier, 65 + 78pp.

P.O. Lax and R.D. Richtmyer (1956): Survey of the stability of linear limite difference equations, Comm. Pure Appl. Math., vol.9, p.267-293.

R. Lefever and G. Nicolis (1971): Chemical InstabiLities and sustained oscillotions, J. theor. Bioi., vol30, p267-284.

G.W. Leibniz (1691): Methodus, qua innummerarum linearum construction ex data proprietate tangentium seu aequatio inter abscissam et ordinatam ex dato valo~ subtangentitlli.s, exhibetur. Letter to Huygens, in: C.l Gerhardt, Leibnizens math. Schriften, 1850, Band II, p.116-121.

G.W. Leibniz (1693) (Gothofredi Guilielmi Leibnitzii): Supplementum Geometriae Dimensoriae seugenerali.ssima omnium tetra gonismorum ef!ectio per motum: Similiterque multiplex constructio linea ex data tangentium condi­tione, Acta Eruditorum, Lipsiae, p.385-392; german translation: G. Kowalewski, Leibniz uber die Analysis des Unendlichen, Oltwalds Klassiker Nr.162 (1908), p24-34.

A.M. Liapunov (1892): Probleme general de /Q stabilite du mouvement, russ., trad. en fran~ais 1907 (Annales de la Faculte des Sciences de Toulouse), reprinted 1947 Princeton Univ. Press, 474pp.

A.M. Lienard (1928): Etude des osciJiations entretenues, Revue ~nerale de l'Elec­tricite, tome XXIII, p. 901-912 et 946-954.

E. Lindelof (1894): Sur !application des methodes d'approximation successives a t etude des intigrales reelles des equations differentieUes ordinaires, J. de Math., 4e serie, vol.lO, p.l17-128.

J. Liouville (1836): Sur le diveloppement des fonctions ou parties de fonctions en series dont les divers termes sont assujetis a satisfaire a une meme equation differentielle du second ord~. contenant un parametre variable, Joum. de Math. pures et appl., vol.l, p253-265.

J. Liouville (1838): Sur /Q Theorie de /Q variation des constantes arbitraires, Liou­ville J. de Math. vol3, p342-349.

Page 33: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

466 Bibliography

J. Liouville (1841): Remarques nouveUes sur /'equation de RiccDti, J. des Math. pures et 8{l)l., vol.6, p.1-13.

R. Lipschitz (1876): Sur Ia possibilite d'intigrer compli!tement un sysfeme donne d'equations differentielles, Bulletin des Sciences Math. et Astr., Paris, vol.10, p.149-159.

R. Lobatto (1852}: Lessen over Differentiaal- en lntegraai-Rekening, 2 vol., La Haye 1851-52.

E.N. Lorenz (1979): On the prevalence of aperiodiciJy in simple systems, Global Analysis, Calgary 1978, ed. by M.Grmela and J.E.Marsden, Lecture Notes in Mathematics, vol.755, p.53-75.

M. Lotkin (1951): On the accuracy of Runge-Kutta methods, MTAC vol5, p.128-132.

G.l. Marchuk (1975): Prostejshaya matematicheskaya model vi1usnogo zabolevaniya, Novosibirsk, VI'S SO AN SSSR. Preprint.

G.L Marchuk (1983}: Mathematical models in immunology. Translation series, ~on Software, New York, Springer Verlag, 351pp.

M. Marden (1966): Geometry of polynomials, American Mathematical Society, Pro­vidence, Rhode Island, 2nd edition.

J.E. Marsden and M. McCracken (1976): The Hopf bifurcation and its applications, Springer, New York, 408pp.

R.M. May (1976): Simple mathematical models with very comp/Jcated dynamics, Nature, vol261, p.459-467

R.H. Merson (1957): An operational method for the study of integration processes, Proc. Symp. Data Processing, Weapons Research Establishment, Salis­bury, Australia, p.ll0-1 to 110-25.

W.E. Milne (1926): Numerical integration of ordinary differential equations, Amer. Math. Monthly, vol33, p.455-460.

W.E. Milne (1970): Numerical solution of differential equations. Dover Publica­tions, Inc., New York, second edition.

R. von Mises (1930): Zur numerischen Integration von Differentialgleichungen, ZAMM, vol.lO, p.81-92.

A.R. Mitchell and J.W. Craggs (1953): Stability of difference relations in the solution of ordinary differential equations, Math. Tables Aids Com put., vol.7, p.127-129.

C. Moler and C. Van Loan (1978): Nineteen dubious ways to compute the exponen­tial of a matrix; SIAM Review, Vol20, p.801-836.

R.E. Moore (1966): Interval Analysis, Prentice-Hall, Inc, 145pp. R.E. Moore (1979): Methods and applications of interval analysis, SIAM studies in

Appl. Math., 190pp. F .R. Moulton ( 1926): New methods in exterior ballistics. Univ. Chicago Press. M. Mnller (1926): Ueber dos Fundamentaltheorem in der Theorie der gewiJhnlichen

DUJerentialgleichungen, Math. Zeitschr., vol26, p.619-645. (Kap.Ill). E.H. Neville (1934): Iterative interpolation, Ind. Math. Soc. J. Vol20, p.87-120. I. Newton (1671}: Methodus Fluxionum et Serierum Infinitarum, edita Londini

1736, Opuscula mathematica vol.I, Traduit en fran.yais par M.de Buffon, Paris MDCCXL.

Page 34: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Bibliography 467

I. Newton (1687): Philosophiae natura/is principia mathematica, Imprimatur S. Pepys, Reg. Soc. Praeses, juHi 5, 1686, Londini anno MDCLXXXVll.

S.P. Nt'lrsett and G. Wanner (1979): The real-pole sandwich for rational approxima­tions and oscillation equations, BIT vol.19, p.79-94.

S.P. Nbtsett (1974a): One-step methods of Hermite type for numerical integration of stiff systems, BIT, vol.14, p.63-77.

S.P. Nbmett (1974b): Semi explicit Runge-Kutta methods, Report No.6/74, ISBN 82-7151-009-6, Dept. Math. Univ. Trondheim, Norway, 68+7pp.

A. Nordsieck (1962): On numerical integration of ordinary differential equations, Math. Comp., vol.16, p.22-49.

B. Numerov (B.V.Noumerov) (1924): A method of extrapolation of perturbations. Monthly notices of the Royal Astronomical Society, vol.84, p.592-601.

B. Numerov (1927): Note on the numerical integration of d2x /dt2=J (x ,t ). Astron. Nachrichten, vol.230, p359-364.

E.J. Nystrom (1925): Ueber die numerische Integration von Differentialgleichungen, Acta Soc. Sci. Fenn., vol.50, No.13, p.1-54.

M. Okamoto and K. Hayashi (1984): Frequency conversion mechanism in enzymatic feedback systems, J. Theor. Bioi., vol.108, p.529-537.

J. Oliver (1975): A curiosity of low-order explicit Runge-Kutta methods, Math. Comp., vol.29, p.1032-1036.

M.R. Olbome (1966): On Nordsieck's method for the numerical solution of ordinary differential equations, BIT, vol.6, p.51-57.

B.N. Parlett (1976): A recu"ence among the elements of functions of triangular matrices, linear Algebra Appl., vol.14, p.117-121.

G. Peano (1888): Integration par series des equations dijferentieU.es lineaires, Math. Annalen, vol.32, p.450-456.

G. Peano (1890): Demonstration de l'integrabilile des equations differen.tielles ordi­naires, Math. Annalen vol.37, p.l82-228; see also the german transla­tion and commentation: G. Mie, Math. Annalen vol.43 (1893), p.553-568.

G. Peano (1913): Resto neUe formule di quadratura, espresso con un integrate dejiniJo, Atti Della Reale Accad. Dei Uncei, Rendiconti, vol.22, N.9, p.562-569, Roma.

R. Pearl and LJ. Reed (1922): A further note on the mathematicoltheory of popula­tion growth, Proceedings of the National Acad. of Sciences, vol.8, No.12, pp.365-368.

L.M. Perko (1984): Limit cycles of quadratic systems in the plane, Rocky Mountain J. of Math., vol.14, p.619-645.

0. Perron (1915): Ein neuer Existenzbeweis ftlr die Integra/e der Dijferentialgleichung y '=f (x ,y ), Math.Annalen, vol.76, p.471-484.

0. Perron (1918, zur Zeit im Felde): Fin neuer Existenzbeweis fUr die Integrale eines Systems gewohnlicher Differentialgleichungen, Math. Annalen, vol.78, p.378-384.

0. Perron (1929): Ueber Stabililllt und asymptotisches Verhalten der Integrate von Dijferentiolgleichungssystemen, Math. Z., vol.29, p.129-160 (see par. 3).

E. Picard (1890): Memoire sur Ia thiorie des equations aux dhivees partielles et Ia methode des approximations successives, J. de Math. pures et appl., 4e ~rie, vol.6, p.145-210.

Page 35: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

468 Bibliography

E. Picard (1891-96): Traile ffAMlyae, 3 voJs. Paris.

P. Piotrowsky (1969): Stability, consistency and convergt!IICt! of variable k -step methods for tum~ericol ~grot/on of klrge systems of ordinary dilferentilll equations, Lecture Notes in Math., 109, Dundee 1969, p.221-227.

H. Poincar~ (1881,82,85): Sur lea courbea dejiniea par les equations df/fmntiellea, J. de Math., 3e ~rie, t.7, p.375-422, 3e s~rie, t.S, p.251-296, 4e ~rie, t.1, p.167-244.

R Poincar~ (1893): Lea mhhodes nollVelles de Ia mecanique celeste, Tome ll, 480pp, Gauthier-Villars Paris.

S.D. Poisson (1835): Thiorie mathimatique de /Q chaleur, Paris, BacheHer, 532pp., Suppl~ment 1837, 72pp.

B. Van der Pol (1926): On "Relaxation Oscil/o.tlons", Phil. Mag., vol.2, p.978-992; reproduced in: B. van der Pol, Selected Scientific Papers, vol.I, North. Holland Publ. Com.p. Amsterdam (1960).

P. Pouzet (1963): Etude en vue de leur trtJilement numerique des equations integralea de type Volterra, Rev. Fran¢8 Traitement Information ( Chiffres), vol.6, p.79-112.

P J. Prince and J.R. Dormand (1981): High order embedded R unge-Kutta fonnu/oe, J.Comp. Appl. Math. vol.7, p.67-75.

H. Prtlfer ( 1926) : Neue H erleilung der Sturm -L iouvillschen R eihenentwicldung atetiger Funlctionen, Math. Annalen vol. 95, p.499-518.

R. Radau (1880): Elude sur lea formes d'approximation qui servent a ct~lculer Ia valeur numerique d'une integrale dijinie, Liouville J. de Math~. pures et appl., 3eser., tome VI, p.283-336. (Voir p.307).

A. Ralston (1962): Runge-Kutta methods with minimum error bounds, Math. Com­put., vol.16, p.431-437, corr. vol.17, p.488.

Lord Rayleigh (1883): On maintained vibrations, Phil. Mag. Ser.5, vol.15, p.229-235.

W.T. Reid (1980): Sturmian theory for ordinary differential equations, Springer Ver­lag, Awl. Math., Serie31, 559pp.

J. Riccati (1712): Soluzione generale del Problema inverso intomo a raggi oscula­tori, .. , detenninar Ia curva, a cui convengo UM tal' espressione, Giomale de'Letterati d'Italia. vol.ll, p.204-220.

J. Riccati (1723): Animadversiones in aequationes dilferentiales secundi gradus, Acta Erud. Lips., anno MDCCXXIll, p.502-510.

L.F. Richardson (1910): The approximate arilhmetiall solution by finite differences of physical problems including differential equations, with an appliclltion to the stresses in a masonry dom, Phil. Trans., A, vol.210, p.307-357.

L.F. Richardson (1927): The deferred approach to the limit, Phil. Trans., A, vol. 226, p.299-349.

B. Riemann (1854): Ueber die Darstellbarkeit einer Function durch eine trigono­metrische Reihe, von dem Verfasser behufs seiner Habilitation an der Universitat zu Gottingen der philosophischen Facultat eingereicht; col­lected works pp. 227-265.

W. Romberg (1955): Vereinfachte numerische Integration, Norske Vid. SeJsk. Forhdl, vol.28, p.30-36.

E. Rothe (1930): ZweidimensioMle parabolische Randwertaufgaben a/s GrenifaU ein­dimensioNJler Randwertaufgaben, Math. Annalen, vol. 102, p. 650-670.

Page 36: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Bibliography 469

N. Rouche, P. Habetsand and M. Laloy (1977): Stability theory by LiaputWV's direct method, Appl. Math. Sci. 22, Springer Verlag, 396pp.

E.J. Routh (1877): A Treatise on the stability of a given state of motions, being the essay to which the Adams prize was adjudged in 1877, in the Univer­sity of Cambridge. London 108pp.

E.J. Routh (1884): A Treatise on the dynamics of a system of rigid bodies, part I and II, 4th edition (1st ed. 1860, 6th ed. 1897, german transJation with remarks of F.Klein 1898).

D. Ruelle and F. Tak.ens (1971): On the nature of turbulence, Commun. Math. Physics, vol20, p.167-192.

C. Runge and H. Konig (1924): Vorlesungen Uber numerisches Rechnen, Grund­lehren XI, Springer Verlag, 372pp.

C. Runge (1895): Ueber die numerische AujlDsung von Differentialgleichungen, Math. Ann., vol.46, p.167-178.

C. Runge (1905): Ueber die numerische AujlDsung totaler Differentialgleichungen, Gottinger Nachr., p252-257.

H. Rutishauser (1952): Ueber die lnstabililiJt von Methoden zur Integration gewDhn­licher Differentialgleichungen, ZAMP, vol.3, p.65-74.

D. Sarafyan (1966): Error estimation for Runge-Kutta methods through pseudo­iterative formukJs; Techn. Rep. No14, Lousiana State Univ ., New Orle­ans, May 1966.

L. Scheeffer (1884): Zur Theorie der stetigen Funktionen einer reeUen VerDnder­lichen, Acta Mathematica, vol.5, p.183-194.

I. Schur (1909): Ueber die charakteristischen Wurzeln einer linearen Substitution mit einer Anwendung auf die Theorie der lntegralgleichungen, Math. Ann., vol.66, p.488-510.

L.F. Shampine (1979): Storage reduction for Runge-Kutta codes, ACM Trans. Math. Software, Vol.5, p.245-250.

L.F. Shampine and L.S. Baca (1984): FixNJ vs. variable order Runge-Kutta, Rept. SAND84-1410, Sandia Nat'l Labs., Albuquerque, New Mexico, 57pp.

L.F. Shampine and M.K. Gordon (1975): Computer Solution of Ordinary Differential Equations, The Initial Value Problem, Freeman and Com­pany, San Francisco, 318pp.

L.F. Shampne and HA. Watts (1979): The art of writing a Runge-Kutta code. II, Appl. Math. Comput., vol.5, p.93-121.

L.F. Shampine, HA. Watts and S.M. Davenport (1976): Solving nonstiff ordmory differential equations- The state of the art, SIAM Rev. vol.18, p.376-410.

E.B. Shanks (1966): Solutions of differential equations by evaluotions of functioN, Math. of Comp. vol.20, p.21-38.

D. Sommer (1965): Numerische Anwendung impliziter RungeJutta-Formeln, ZAMM, vol. 45, Sonderheft, p. T77-T79.

Shi Songling ( 1980): A concrete example of the existence of four limit cycles for plo.ne quadratic systems, Sci. Sinica, vol23, p.153-158.

G.F. Simmons (1972): Differential equations with applications and historical nates, MC Graw-Hill, 465pp.

R. Skeel (1976): Analysis ofjixed-stepsize methods, SIAM J. Numer. Anal., vol.13, p.664-685.

Page 37: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

470 Bibliography

R.D. Skeel ( 1978): Equivalent forms of multistep formukJs, Report R-78-940, Dept. of Comp. Sci., Univ. of Illinois at Urbana-Champaign.

M.N. Spijker (1971): On t1u! s~ of error estimates for finite di;Jference methods. Numer. Math., vol.18, pp.73-100.

J.F. Steffensen (1956): On tlu! restricted problem of tlwe bodies, K. danske Viden­sk. Selsk., Mat-fys. Medd. 30 Nr.18.

HJ. Stetter (1970): Symmetric two-step algorithms for ordinary di;Jferential equations, Computing vol.S, p267-280.

HJ. Stetter (1973): Analysis of discretization methods for ordinary differential equa­tions, Springer Verlag, Berlin-Heidelberg-New York.

C. Stormer (1907): Sur les tmjectoires des corpuscules e/ectrises. Arch. sci. phys. nat., Gen~ve, vol.24, p.S-18, 113-158, 221-247.

C. Stormer (1921): Methodes d'integration numerique des equations di;Jfbentiel/es ordinaires. C.R. congr. intern. math., Strasbourg, p243-257.

J. Stoer and R. Bulirsch (1973): Einfllhrung in die numerische Mathematik, Springer VerJag, 1st ed. 1973, English translation 1980 (see section 7 .3.5).

J. Stoer and R. Bu1irsch (1980): Introduction to Numerical Analysis, Springer Ver­Jag, 609pp., german edition 1973.

C. Stoermer (1907): Sur lea tmjectoires des co~s e/eclrish, Arch. sci. phys. nat., Gen~ve, vol.24, p.S-18, 113-158, 221-247.

C. Stoermer (1921): Methodes d'wegration numerique des equations di;Jferentiel/es ordinaires, C.R. congr. intern. math., Strasbourg, p.243-257.

A.H. Stroud and D.O. Stancu (1965): Quadmture formukJs wilh multiple Gaussian nodes, SIAM J. Numer. Anal., ser.B., vol2, p.129-143.

Ch. Sturm (1829): Bulletin des Scil!nces de Ferussac, tome XI, p.419, see also: .Aigebre de Choquet et Mayer (1832).

Ch. Sturm (1836): Sur lea equations di;Jferentielles lineaires du second ordre, Journal de Math. pures et appl. (Liouville), vol.l, p.106-186 (see also p.253, p269, p.373 of this volume).

J. Todd (1950): Notes on modem numerical analysis, I, Math. Tables Aids Com­put., vol.4, p.39-44.

W. Tollmien (1938): Ueber die FehlerabschiJtzung beim Adam88chen Vetfahren zur Integration gewDhnlicher Dflferentialgleichungen, ZAMM, vol.18, p.83-90.

W. Tomson (Lord Kelvin) and P.G.Tait (1879): Treame on natural philosophy (Voi.I., Part I), Cambridge; New edition 1890, 508pp.

W. Uhlmann (1957): Feh/erabsch/Jtzungen bei Anfangswertaufgaben gewDhnJicher Differenlialg/eichungssysteme 1. Orr:lnung, ZAMM (Zeitschr. Angew. Math. Mech.) vol.37, p.SS-99.

P.F. Verhulst (1845): Recherches mathhnatiques sur Ia loi d'accroi8sement de Ia po­pulation, Nuov. Mem. Acad. Roy . .Bruxelles, vol.18, p.3-38.

J.H. Verner (1978): Explicit Runge-Kutta methods with estimates of tlu! local trunca­tion error, SIAM J.Numer. Anal. vol.15, p.772-790.

L. Vietoris (1953): Der Richtungsfehler einer durch das Adamssche Interpola­tionsverfahren gewonnenen Naherungslosung einer Gleichung y '= f (x ,y ). Oesterr. Akad. Wiss., Math.-naturw. Kl., Abt. Ila, vol.162, p.157-167 and p293-299.

V. Volterra (1934): Remarques sur Ia Note tk M. Regnier et Mile Lambin. C.R.Acad. Sc. t. CXCIX, p.1682. See also: V.Volterra - U.d' Ancona , Les associations biologiques au point de vue math~matique, Paris 1935.

Page 38: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Bibliography 471

W. Walter (1970): Differential and integral inequalitii!s, Springer Verlag 352 p., ger­man edition 1964.

W. Walter (1971): There is an elementary proof of Pean.o's existence theorem, Amer. Math. Monthly, vol.78, p.170-173.

G. Wanner (1969): Integration gewl>hnlicher Di.fferentialgleichwtgen, Li£ Reihen, Run.ge-Kutll.l-Methoden., BI Mannheim Htb. 831/831a, 182pp.

G. Wanner (1973): Run.ge-Kutta methods with expansions in even powers of h, Computing vol.ll, p.81-85.

G. Wanner (1983): On Shis counter example for the 16th Hilbert problem, Internal Rep. Sect. de Math., Univ. Gen~ve 1982; in german in: Jahrbuch Ueberblicke Mathematik 1983, ed. Chatterji, Fenyo, Kulisch, Laugwitz, Uedl, BI Mannheim, p.9-24.

H.A. Watts (1983): Storting stepsize for an ODE solver, J. Comp. Appl. Math. vol.9, p.177-191.

K. Weierstrass (1858): Ueber ein di£ homogenen Functionen zweiten Grades betref­fendes Theorem, nebst Anwendung desselben auf die Theorie der kleinen Schwin.gun.gen, Monatsber. der Konigl. Akad. der Wiss., 4. Marz 1858, Werke Bd.l, p.233-246.

J. Weissinger (1950): Eine verschiJrfte FehlerabschiJtzun.g zum Extrapolationsver­fahren von Adams, ZAMM, vol30, p.356-363.

0. Wilde (1892): Lady Windennere's Fan., Comedy in four acts. J.H. Wilkinson (1965): The algebraic eigenvalue problem, Monographs on numerical

analysis, Oxford, 662pp. J.H. Wilkinson and C. Reinsch (1970): Linear Algebra, Grundlehren Band 186,

Springer Verlag, 439 pp. A. Wintner and F.D. Murnaghan (1931) :A tXJnonical fonn for real matrices under

orthogonal tran.sfonnation.s, Proc. Nat. Acad. Sci. U.S.A., vol.17, p.417-420.

E.M. Wright (1945): On a sequence defined by a non-linear recurrencefonnula, J. of London Math. Soc., vol.20, p.68-73.

E.M. Wright (1946): The non-linear dJjferen.ce-di.fferential equation, Olart. J. of Math., vol.17, p.245-252.

E.M. Wright (1955): A non-linear difference-differential equation, Jl.d.r.u. angew. Math., vol.194, p.66-87.

K. Wright (1970): Some relationships between implicit Run.ge-Kutto collocation and Lanczos 'T methods, and their stobility propertii!s, BIT vol.lO, p.217-227.

H. Wronski (1810): ·Premii!r principe des methodes algorithmiques comme base de La technique algorithmique, publication refused by the Acad. de Paris (for more details see: S.Dickstein, Int. Math. Congress 1904, p517).

M. Zennaro (1986): Natural continuous extensions of Run.ge-Kutto methods, Math. Comput. Vol.46, p.119-133.

J.A. :Wnneveld (1963): Automatic integration of ordinory differential equations, Re­port R743, Mathematisch Centrum, Postbus 4079, 1009AB Amster­dam. Appeared in book form 1964.

R. Zurm1lhl ( 1948): R un.ge-K utiiJ-V erfahren zur numerischen Integration von Differ­en.tialgleichun.gen. n-ter Ordnung, ZAMM, vol.28, p.173-182.

R. Zurmohl (1952): Runge-Kutta Veifahren unter Verwendun.g hDherer Ableitungen, Z angew. Math. Mech. vol.32, p.153-154.

Page 39: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

A®I a(t)

B1 (a, y) B(p) b1(e)

ci'ai}'bl c cp+t c ("1) D

D(~)

Symbol Index

tensor product 343 B-series coefficients 243, 244

B-series 244 quadrature order 204 continuous method 179

RK coefficients 132f

error constant 320, 365, 429 local error constant 319

simplifying assumptions 203 differential operator 250 simplifying assumptions 203

D:m(x) Diniderivates 54

d1(t) difference set 244

E principal part of S 392 ep (x) global error coefficient 211, 212

I [x11 , ••• ,x11 _ 1] divided differences 347

F1(t)(y) elementary differential 145,147,264,268,279 g1(n) variable step size coefficients 348

h step size 128f Kq(s)

l=(l0,lp··> L L (y,x ,h) LNTq

LSq

LTq, LT

LTP 8 LTP8 q'

NTq P(c,y) P(EC)M P(EC)M E

Peano-kernel 322

Nordsieck coefficients 361, 367

Lipschitz constant 33, 51 difference operator 316, 427 labelled N-trees 264

special labelled trees 149

labelled trees 145, 243

labelled P-trees 278, 281

N-trees 264

P-series 281 predictor-corrector 388 predictor-corrector 375, 387

Page 40: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

474

IIQ II R (x, xo)

s si(t)

121• 131•··

[ t 1 ' · · · ' 1m] a[11' · · · • 1m)

Tq,T

T.1, T.k I' } '

TP 0 TP 0 q'

v (y 1' • • • 'y II ) W (x)

II Y II yh(x)

Y (x, xo, Yo) z11 =z(x11 , h)

aj, ~j a(t)

~j(n)

'Y(t)

Vi! II

~(Q) cfl(h) ~j(t)

~j(n)

~j(n)

~(xo,Yo,h)

~"'(x,y,h) p(t) p(C), a(t)

Symbol Index

matrix norm 51, 52 resolvent 64

matrix of general linear method 386 sub-tree 244

trees 147

composite tree 152

composite tree 278

rooted trees 146, 243

extrapolation tableau 219, 273

P-trees 278, 281

Liapunov function 87

Wronskian 64 vector norm 50 Euler polygon 32

solution 97

correct value function 386

multistep coefficients 315, 351

coefficient 146, 147, 264, 268, 278 variable step size coefficients 349

order products 147, 150, 268

backward differences 305

logarithmic norm 59 starting procedure 386 weights 150, 266, 268

divided differences 349

divided differences 348

increment function 159, 211, 343, 386, 405

adjoint method 214 order of a tree 145, 147, 268, 278 generating polynomial 317 one-node trees 146, 278

Page 41: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Subject Index:

Abel-Uouville-Jarobi-Cktrogradskii identity 65

Adams methods 305f as Nordsieck methods 360,

363, 367 error oonstant 320 variable step size 347

Adjoint matrix 71 Adjoint method 214

asymptotic expansion 216 general linear methods 412

Aitken-Neville algorithm 221 Arenstorf orbits 128, 197 Asymptotic expansion 212

gen~allinear methods 403f in h 217,226, 416 seoond order equations 429

Asymptotic solutions for small parame-ters 110

Asymptotic stability 89 Autonomous systems 69

B-series 242, 244 Backward differences 305 Backward differentiation formulas

(see BDF) BDF 311,312

as Nordsieck methods 368, 369 stability 328 variable step size 350, 356, 359

Bernoulli equation 13 Bernoulli numbers 365 Besselequation 23 Boundary oonditions 101 Boundary value problems 101 Brachystochrone problem 7, 12, 22 BRUS 237, 238 Brusselator 112, 172, 237

full 114 with diffusion 381

Bulirsch sequence 221 Butcher barriers 189 Butcher's 6-th order method 189 Butcher's Lobatto formulas 205 Butcher's methods of order 2s 203,

204,205

Ceschino's method 168 Characteristic equation 16, 70

delay equations 290 Characteristic polynomial 70 Chemical reactions 111 Oairaut differential equation 8, 13 Collocation methods 206

equivalence to RK 206 order 207 with multiple nodes 251

Collocation polynomial 206 Composition of B-series 245 Composition of RK methods 242 Consistency conditions 318

general linear methods 393 seoond order equations 426

Constant coefficients 69 geometric representation 77 numerical oomputations 72

Continuous RK methods 176 for delay equations 289, 301 for DOPRI5 179

Convergence Euler's method 31 general linear methods 394 multistep methods 340, 344 Nystrom methods 270 RK methods 156 seoond order equations 427 variable step size multistep 357

Convergence monitor 230 Correct value function 386 Corrector 308

Page 42: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

476 Subject Index

Cowell and Crommelin's method 423 Critical points 77, 78 Cyclic multistep methods 389

D-stability 328 D02CAF 378 Dahlquist barrier (first) 326, 332 DEABM 374 Defect 55 Delay differential equations 286

stability 291 Dense output 176 Derivatives

numerical 183 with respect to initial values 97 with respect to parameters 95

Diagonal implicit RK-method 200 Diagonalization 69 DIFEX1 236 Difference equation 27 Differential equation of Laplace 140,

304 Differential inequalities 54

for systems 61 DIFSUB 376 Dini derivatives 54 DIRK-method 200 Discontinuous equations (numerical

study) 180 Discrete Laplace transformation 363 Divided differences 347 DOPRI5 171, 433 DOPRI8 195, 435 DOPRIN 273, 447 Dormand and Prince method 171

continuous extension 179 second order equations 272

Drops 140

Effective order 247 Ehle's methods 210 Eigenfunctions 105 Eigenvalue 69 Eigenvector 69 Elementary differential 145, 264, 268,

279,280

Embedded RK formulas 167 of high order 193

Encke's method 419 End-vertex 264 Enzyme kinetics 295 EPISODE 375 Equivalence of

RK methods 249 labelled trees 146 N-trees 264 P-trees 278

ERK. 132, 200 Error

global 159, 211 local 160, 315, 391

Error coefficients 158 Error constant 319, 320

Nordsieck methods 365 second order equations 429

Error estimate 57, 156 of Euler's method 36 practical 165

Estimation of the global error 159 Euler polygons 6, 32

convergence 31 error estimate 36 for systems 50

Euler's method 6, 32, 306 implicit (backward) 199, 307

Euler-Maclaurin formula 213 Existence theorem 31

for systems of equations 49 of Peano 37 using iteration methods 41 using Taylor series 43

Explicit Adams methods 305, 306 Explicit RK methods 132

arbitrary order 228 high order 185

External stages 390 Extrapolation methods 219

as Runge-Kutta methods 228, 233

order 220 second order equations 271 with symmetric methods 223

FaA di Bruno's formula 148 Father 145

Page 43: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Subject Index 477

Fehlberg's methods 170, 194 multiderivative 254, 283

Feigenbaum cascades 121 number 122

Fll..GR9 273 Forward step procedure 386 Fourier 28 Fundamental lemma 56

GBS method 224, 271 General linear methods 385, 390

convergence 394 order 393 order conditions 396 stability 391

Generating functions for the "/ i 308

Generating polynomials of multistep methods 317

Gerschgorin's theorem 91 Gill's method 138 Global error 159, 211 Gragg's method 224 Greek-Roman transformation 332 Gronwall lemma 61

Hammer and Hollingsworth's method 200, 201, 203

Hanging string 26 Harmonic sequence 221 Heat conduction 28,103 Hermite interpolation 251 Heun's methods 133 Higher derivative methods 250 Hilbert's 16th problem 123 Hopf bifurcation 113 Hybrid methods 385 Hypergeometric functions 22

Immunology 297 Implementation of multistep methods

372 Implicit Adams methods 306, 307

as Nordsieck methods 360, 363, 367, 368

Implicit differential equation 8 Implicit midpoint rule 199, 201 Implicit output 180

Implicit RK methods 199 as collocation methods 206 based on Gaussian formulas 203 based on Lobatto quadrature 204 existence of solution 201

Increment function 159 general linear methods 386

Index equation 21 Infectious disease modelling 294 Infinite series 4 Inhomogeneous linear equation 10

systems 66 mitial value 1 Integro-differential equations 299 Internal stages 390 Inverse tangent problem 6 IRK-method 200 Irreducible methods 321

JACB 236, 238 Jacobian elliptic functions 236 Jordan canonical form 74 Josephson junctions 115, 116

Kronecker tensor product 343 Kuntzmann's methods of order 2s

203,204,205 Kutta's 3/8 rule 137

Labelled N -tree 263 Labelled P-tree 278 Labelled tree 145 Lady Windermere's Fan 35, 99, 160,

345 LAGR 237, 238 Lagrange 25 Large parameters 109 Uapunov functions 87 Umit cycle 107, 113

existence proof 107 unicity 124

Unear differential equations 15 homogeneous 15 inhomogeneous 16,17,66 systems 63 weak singularities 20 with constant coefficients 15, 69

Page 44: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

478 Subject Index

Linear multistep formulas 304 convergence of order p 341 general 315

Lipschitz condition 33, 340 one-sided 58

Local error 160, 211 general linear methods 391 multistep 315 numerical estimation 372

Local extrapolation 196 Logarithmic norm 59, 62 Lorenz model 117, 118 LSODE 376

Madam Imhof's cheese pie 331 Maprant method 44 Matrix norms 51 Merson's method 169 Method of tines 3, 381 Midpoint rule 130, 309

implicit 199 Milne-Simpson methods 310 Multi-step multi-stage multi-derivative

methods 391 Multiderivative methods 250, 253,

391 order conditions 256

Multiple characteristic values 19 Multistep formula

as general linear method 387 characteristic equation 326 cyclic 389 generalized 385 irreducible 321 modified 385 parasitic solution 327 Peano kernel 322 stability 326, 328 symmetric 335 variable step size 347

N-tree of order q 264 Newton's interpolation formula 305,

347 Nonlinear variation-of-constants for­

mula 98 Nordsieck methods 360f

as general linear methods 389 equivalence with multistep 363

Nordsieck vector 360, 369 Norm 50

logarithmic 59 of a matrix 51

Normal matrices 80 Numerical examples

comparisons of codes 236 extrapolation methods 222 4th order methods 139, 174 high order methods 196 multistep codes 378 second order equations 273

Numerov's method 423 Nystrom methods

construction 268 convergence 270 general linear methods 391 multistep 309 order conditions 267, 283

Oxeschkoff methods 253 ODEX 236, 440 ODEX2 273, 443 One-sided Lipschitz condition 58 One-step methods 127, 211 Optimal formulas 137 Optimal order

extrapolation 229 multistep 374

Order Adams methods 318, 319 extrapolation methods 220 general linear methods 393 labelled tree 145 multistep methods 317 RK methods 133 variable step size multistep 351

Order barriers (Butcher) 185, 189 Order barriers (Dahlquist) 332, 429 Order conditions

general linear methods 396 multiderivative methods 256 multistep 315, 317 number of 153 Nystrom methods 267, 268 RK methods 142, 144, 153, 247

Order control extrapolation 228, 232 multistep 372

Page 45: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Subject Index 479

Oregonator 114, 115 Orthogonal matrix 71

P-series 281 P-trees 277, 278, 280 Parasitic solution 327 Partial differential equations 3, 381 Partitioned systems 255, 276 Peano kernel 322 Pendulum equation 124 Perimeter of the ellipse 23 Periodic solution 107 Phase-space 77 Picard iteration 42

for systems 52 PLEI 237, 238, 239 Pleiades problem 237 Poincare sections 107, 120

computations 180 Population dynamics 292 Preconsistency conditions 397 Predictor-corrector process 307, 387 Prince and Dormand's method 195

at high tolerances 197 Principal error term 158 Principle of the argument 330 Propagation of sound 25 Pseudo Runge-Kutta methods 385

q-derivative RK method 250 Quasimonotone 61

Radau scheme 199 Rational extrapolation 221 Recurrence relations for the 'Y i 308 Regular singular point 22 Resolvent 64 REfARD 289, 450 Retarded arguments 286 Riccati equation 41 Richardson extrapolation 165, 177 Rigorous error bounds 156 Romberg sequence 221 Root of a tree 145 Root condition 328

Rothe's method 3, 381 Rounding error reduction 430 Routh tableau 85, 86

computation 86 Routh-Hurwitz criterion 82 Runge's methods 133 Runge-Kutta methods

delay 288 diagonal implicit 200 explicit 132f general formulation 132, 142 implicit 199' 200 of order four 133 singly diagonal implicit 200 ''the" 137 violating (1.9) 282

Schur decomposition 70 Schur norm 52 Schur-Cohn criterion 336 SDIRK-method 200

order three 203 Second order equations 11,

extrapolation methods 271 multistep methods 418f Nystrom methods 261£ Runge-Kutta methods 260

Shooting method 102 Simplifying assumptions 134, 203, 401 Singularities 20 SN-trees 267, 268 Son 145 Son-father mapping 145 Special labelled trees 149 Spherical pendulum 113 Stability

asymptotic 89 BDF 328 delay equations 291 general linear methods 391 multistep formula 326 non-autonomous systems 90 nonlinear systems 89 second order equations 424 variable step size multistep 352

Stable in the sense of Liapunov 81 Starting procedure 304, 386 Starting step size 182

Page 46: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

480 Subject Index

Steady-state approximations 109 Steam engine governor 92 Step size control 166

extrapolation methods 228, 232 multistep methods 372 numerical study 172, 232

Step size freeze 183 Step size ratio 352, 372 Stoermer's methods 273, 419, 423 Strange attractors 117 Strictly stable methods 405 Sturm sequence 83 Sturm's comparison theorem 103 Sturm-Uouville eigenvalue problems

103 Subordinate matrix norms 51 Symmetric methods 216

asymptotic expansion 217 general linear methods 415 multistep 335

Systems of equations 25 autonomous 69 linear 63 second order 260 with constant coeffi::ients 69

Taylor expansion of exact solutions 144, 146 of RK solutions 131, 143, 150

Taylor series 42 convergence proof 44 recursive computation 45

Three body problem 127 Three-eighth's rule 137

Trme lags 286 Total differential equation 10 Trapezoidal rule 199 Tree 146

number of 147 Two body problem 236 lWOB 236, 238

Unitary matrix 71

Van der Pol's equation 107, 236 Variable step size

Adams 347 BDF 350 multistep methods 347f

Variation of constants 17, 66 nonlinear 98

Variational Calculus 7 Variational equation 97 VDPL 236,238 Vector notation 2, 50 Vibrating string 25

Weak singularities 20 for systems 67 RK methods applied to 164

Weakly stable methods 411 Work-precision diagrams 139, 175,

181,196,197,222,227,240,274, 379,380,384

Wronskian 18, 64

Zero-stability 328 Zonneveld's method 169

Page 47: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Springer Series in Computational Mathematics Editorial Board: R. L. Graham, J. Stoer, R.Varga

Springer-Verlag Berlin Heidelberg New York London Paris Tokyo

Volume 7 D.Braess

Nonlinear Approximation Theory 1986. 38 figures. XIV, 290 pages. ISBN 3-540-13625-8

Contents: Preliminaries. -Nonlinear Approximation : The Functional Analytic Approach. - Methods of Local Analysis. - Methods of Global Analysis. - Rational Ap­proximation. - Approximation by Exponential Sums. -Chebyshev Approximation by y-Polynomials. - Approx­imation by Spline Functions with Free Nodes. -Appendix: The Conjectures of Bernstein and Erdos. - Bibliography. -Index.

Volume 6 F.Robert

Discrete Iterations A Metric Study Translated from the French by Jon Rokne

1986. 126 figures. XVI, 195 pages. ISBN 3-540-13623-1

Contents: Discrete Iterations and Automata Networks: Basic Concepts. - A Metric Tool. - The Boolean Perron­Frobenius and Stein-Rosenberg Theorems. - Boolean Contraction and Applications. - Comparison of Operating Modes. - The Discrete Derivative and Local Convergence. - A Discrete Newton Method. - General Conclusion. -Appendices 1- 4.- Bibliography. -Index.

VolumeS V. Girault, P.-A. Raviart

Finite Element Methods for Navier-Stokes Equations Theory and Algorithms

1986. 21 figures. X, 374 pages. ISBN 3-540-15796-4

Contents: Mathematical Foundation of the Stokes Problem.- Numerical Solution of the Stokes Problem in the Primitive Variables. -Incompressible Mixed Finite Element Methods for Solving the Stokes Problem. -Theory and Approximation of the Navier-Stokes Problem. -References. - Index of Mathematical Symbols. - Subject Index.

Page 48: APPENDIX. FORTRAN CODES - link.springer.com978-3-662-12607-3/1.pdf · APPENDIX. FORTRAN CODES ... but the software is in various states of development from experimental (a euphemism

Springer Series in Computational Mathematics Editorial Board: R. L. Graham, J. Stoer, R.Varga

Springer-Verlag Berlin Heidelberg New York London Paris Tokyo

Volume4 W.Hackbusch

Multi-Grid Methods and Applications 1985. 43 figures, 48 tables. XIV, 377 pages. ISBN 3-540-12761-5

Contents: Preliminaries. - Introductory Model Problem. -General Two-Grid Method. -General Multi-Grid Iteration. -Nested Iteration Technique. - Convergence of the Two-Grid Iteration. - Convergence of the Multi-Grid Iteration. -Fourier Analysis.- Nonlinear Multi­Grid Methods. - Singular Perturbation Problems. -Elliptic Systems. -Eigenvalue Problems and Singular Equations. -Continuation Techniques. - Extrapolation and Defect Correction Techniques. ­Local Techniques. - The Multi-Grid Method of the Second Kind. -Bibliography. - Subject Index.

Volume 3 N.Z.Shor

Minimization Methods for Non-Differentiable Functions Translated from the Russian by K C. Kiwiel, A Ruszczyilski

1985. VIII, 162 pages. ISBN 3-540-12763-1

Contents: Introduction. - Special Classes ofNondifferentiable Func­tions and Generalizations of the Concept of the Gradient. - The Sub­gradient Method. - Gradient-type Methods with Space Dilation. -Applications of Methods lor Non smooth Optimization to the Solution of Mathematical Programming Problems.- Concluding R emarks. ­References. - Subject Index.

Volume 2 J. R. Rice, R. F. Boisvert

Solving Elliptic Problems Using ELLPACK 1985. 53 figures. X, 497 pages. ISBN 3-540-9091().9

Contents: The ELLPACKSystem. - The ELLPACKModules. ­Performance Evaluation. - Contributor's Guide. - System Program­ming Guide. -Appendices. - Index.

Volume I

QUAD PACK A Subroutine Package for Automatic Integration

By R. Piessens, E. de Doncker-Kapenga, C. W. Oberhuber, D. K. Kahaner

1983. 26 figures. VIII, 301 pages. ISBN 3-540-12553-1

Contents: Introduction. -Theoretical Background. - Algorithm Descriptions.- Guidelines for the Use ofQUADPACK - Special Applications of QUA.DPACK - Implementation Notes and Routine Listings. - References.