From Eudora Zips 07/30/2006 04:45p exp(-alpha x) 07/30/2006 04:42p modifications. 07/30/2006 04:45p different exponential. 07/30/2006 08:38a produce aigau. 11,804 tfun.zip – The final codes described in #Decay as 2,389 tests.zip – test.f from steve and test.for with minimal 1,711 tglagu.zip – code for integrating a polynomial and a 2,931 orig.zip – copy of code for integrating a Gaussian to I modified the Gauss Laguerre code to calculate an integral whose value I know (in this case 1/(x*x+100)^1.5 from 2 to infinity. The exact result is 0.00803884 but the numerical results are off. Here's the code. There is no input. Steve Alexander test.f I compiled this using Watcom wfl386 test.f test 0.0079439532626720 0.0065542826199757 Two different results, neither equal to the actual answer See discussion in #The test function. I changed to the best alpha – bob’s changes to test.f are in lower case - found in the section #Decay as exp(-alpha x) and saved this as test.for Wfl386 test.for test 0.0080365285494317 0.0080100288655011 The results below are more accurate due to the fact that they have 16 digit values of the Gauss Laguerre quadrature points, but the primary problem at this point is that the integrand falls off as x3 which is quite different from the exponential decay assumed by Gauss Laguerre. We can subtract a 1/x3 and integrate it analytically, but that goes beyond the notion of easy quadrature. Bob http://www.phys.ufl.edu/~coldwell/aigau/aiglz/Welcome.htm “TGLAGU.FOR is set up to test Gauss Laguerre integration on an analytic function. obsolete will need revision to be used.” I started in C:\public_html\aigau\aiglz> All fortran and ide files were copied to the present folder aiglz.wpj The main code is AiGlz.for IMPLICIT REAL*8 (A-H,O-Z) DATA SQRPI/1.772453850905516D0/ DATA N/500/ OPEN(1,FILE='BRACK.OUT') OPEN(2,FILE='AIGAUSS.OUT') OPEN(3,FILE='ERR.OUT') DO I=1,N Z=-7+(I-1)*6/(1D0*N) BR=BRGLAG(Z,ERR) AT2=-EXP(-Z*Z)*BR/(2*Z*SQRPI) WRITE(1,'(3G24.16)')Z,BR,ERR WRITE(2,'(3G24.16)')Z,AT2,ERR WRITE(3,'(2G15.6)')Z,ABS(ERR) ENDDO END C$INCLUDE BRGLAGU C$INCLUDE GLAGU The BR refers to AiGauss( z ) exp z 2 Brack z in C:\public_html\aigau\aiglz\Welcome.doc t2 exp t exp 2 dt 4 z (1) Brack z 0 2z Note that z < 0 in this accounting for the – in the definition of AT2 above. The file BRGLAGU.FOR FUNCTION BRGLAG(Z,ERT) IMPLICIT REAL*8 (A-H,O-Z) COMMON/PASS/ZP EXTERNAL AIGI ZP=Z IF(Z.EQ.0)THEN BRGLAG=.5D0 ERT=0 RETURN ENDIF BRGLAG=GLAGU1(AIGI,DIFF) ERT=DIFF/BRGLAG END FUNCTION AIGI(T) IMPLICIT REAL*8 (A-H,O-Z) COMMON/PASS/Z ARG=T/(2*Z) AIGI=EXP(-ARG*ARG) C NOTE THAT THE EXP(-T) IS PART OF GLAG INTEGRAND RETURN END This code uses the function exp t 2 / 4 z 2 so that the full integral is N 0 i 1 2 2 2 2 exp t exp t / 4 z dt wi exp xi / 4 z (2) This is evaluated in GLAGU.FOR 2 3 4 5 6 7 8 9 A B C D E 2 3 4 5 6 7 8 9 A B C D E FUNCTION GLAGU1(FUN,DIFF) IMPLICIT REAL*8 (A-H,O-Z) DIMENSION XI1(19),AI1(19),XI2(20),AI2(20) DATA (XI1(I),AI1(I),I=1,19)/7.415878375720509D-2, .1767684749159125D0,.3912686133199946D0,.3004781436072544D0, .9639573439979580D0,.2675995470381750D0,1.796175582068328D0, .1599133721355802D0,2.893651381873784D0,.6824937997614911D-1, 4.264215539627766D0,.2123930760654432D-1,5.918141561644049D0, .4841627351148396D-2,7.868618915334734D0,.8049127473813668D-3, 10.13242371681527D0,.9652472093153502D-4,12.73088146384240D0, .8207305258051031D-5,15.69127833983589D0,.4830566724730773D-6, 19.04899320982355D0,.1904991361123286D-7,22.85084976082948D0, .4816684630928062D-9,27.16066932741145D0,.7348258839551144D-11, 32.06912225186224D0,0.6202275387572616D-13,37.71290580121965D0, .2541430843015423D-15,44.31736279583150D0,.4078861296825712D-18, 52.31290245740438D0,.1707750187593837D-21,62.80242315350038D0, .6715064649908190D-26/ DATA (XI2(I),AI2(I),I=1,20)/.7053988969198875D-1, .1687468018511139D0,.3721268180016114D0,.2912543620060683D0, .9165821024832736D0,.2666861028670013D0,1.707306531028344D0, .1660024532695068D0,2.749199255309432D0,.7482606466879237D-1, 4.048925313850887D0,.2496441730928322D-1,5.615174970861617D0, .6202550844572237D-2,7.459017453671063D0,.1144962386476908D-2, 9.594392869581097D0,.1557417730278120D-3,12.03880254696432D0, .1540144086522492D-4,14.81429344263074D0,.1086486366517982D-5, 17.94889552051938D0,.5330120909556715D-7,21.47878824028501D0, .1757981179050582D-8,25.45170279318691D0,.3725502402512321D-10, 29.93255463170061D0,.4767529251578191D-12,35.01343424047900D0, .3372844243362438D-14,40.83305705672857D0,.1155014339500399D-16, 47.61999404734650D0,.1539522140582344D-19,55.81079575006390D0, .5286442725569158D-23,66.52441652561575D0,.1656456612499023D-27/ GLAGU0=0 DO I=1,19 GLAGU0=GLAGU0+AI1(I)*FUN(XI1(I)) ENDDO GLAGU1=0 DO I=1,20 GLAGU1=GLAGU1+AI2(I)*FUN(XI2(I)) ENDDO DIFF=GLAGU1-GLAGU0 RETURN END These were checked before, I zip them into orig.zip Test power of x C:\public_html\class2K\integration\GaussLag.doc The code TGLAGU.FOR is set up to test the integrals of powers of x. The relevant portions are 5 IMPLICIT REAL*8 (A-H,O-Z) COMMON /PPOWOF/NPOW COMMON /EXPON/ALPHA EXTERNAL POWOFX,EXPONF PRINT*,' ENTER THE POWER OF X' READ(*,*)NPOW ANFAC=1 DO I=2,NPOW ANFAC=ANFAC*I ENDDO IF(NPOW.EQ.-10)GOTO 10 TEST=GLAGU(POWOFX,DIFF) PRINT*,' TEST=',TEST PRINT*,' NFAC=',ANFAC PRINT*,' DIFF=',DIFF GOTO 5 … FUNCTION POWOFX(X) IMPLICIT REAL*8 (A-H,O-Z) COMMON /PPOWOF/NPOW POWOFX=X**NPOW RETURN END Glagu was changed so that the function is GLAGU rather than GLAGU1 as for the error function integral. Note that the integral of xN is N!. run ENTER THE POWER OF X 0 TEST= 1.000000000000000 NFAC= 1.000000000000000 DIFF= -1.110223024625160D-016 ENTER THE POWER OF X 5 TEST= 120.000000000000000 NFAC= 120.000000000000000 DIFF= 1.421085471520200D-014 ENTER THE POWER OF X 10 TEST= 3628800.000000000000000 NFAC= 3628800.000000000000000 DIFF= 0.000000000000000 ENTER THE POWER OF X 15 TEST= 1.307674368000000D+012 NFAC= 1.307674368000000D+012 DIFF= 0.000732421875000 ENTER THE POWER OF X The first difference is due to the truncation error for 16 digits ENTER THE POWER OF X 20 TEST= 2.432902008176640D+018 NFAC= 2.432902008176640D+018 DIFF= 4608.000000000000000 ENTER THE POWER OF X 25 TEST= 1.551121004333100D+025 NFAC= 1.551121004333100D+025 DIFF= 3.435973836800000D+010 ENTER THE POWER OF X 30 TEST= 2.652528598121910D+032 NFAC= 2.652528598121910D+032 DIFF= 5.404319552844600D+017 ENTER THE POWER OF X 35 TEST= 1.033314796638610D+040 NFAC= 1.033314796638610D+040 DIFF= 1.088033237653170D+025 ENTER THE POWER OF X Note that these last values are still exact, even though the differences indicate only 15 digits. They should be exact until about 36 for 19 points and 38 for 20 points. 40 TEST= 8.159152832419790D+047 NFAC= 8.159152832478980D+047 DIFF= 4.499026736539390D+039 – 8 digits ENTER THE POWER OF X 45 TEST= 1.196221877898960D+056 NFAC= 1.196222208654800D+056 DIFF= 1.159802700720010D+051 – 5 digits ENTER THE POWER OF X 50 TEST= 3.041191034335690D+064 NFAC= 3.041409320171340D+064 DIFF= 2.275593042063180D+061 – 3 digits ENTER THE POWER OF X Test alpha 10 PRINT*,' ENTER ALPHA' READ(*,*)ALPHA IF(ALPHA.GT.2D0)STOP TEST=GLAGU(EXPONF,DIFF) PRINT*,' TEST=',TEST PRINT*,' ANAL=',-1/ALPHA PRINT*,' DIFF=',DIFF GOTO 10 END … FUNCTION EXPONF(X) IMPLICIT REAL*8 (A-H,O-Z) COMMON /EXPON/ALPHA ALPHAP=ALPHA+1 ARG=ALPHAP*X IF(X.GT.90D0)THEN EXPONF=1.22D39 RETURN ENDIF IF(X.LT.-90.D0)THEN EXPONF=0D0 RETURN ENDIF EXPONF=EXP(ARG) RETURN END e x dx 1 e x e 1 x dx 0 Note that alpha must be less than 1 for the integral to converge. 0 ENTER THE POWER OF X -10 ENTER ALPHA -1 TEST= 1.000000000000000 ANAL= 1.000000000000000 DIFF= -1.110223024625160D-016 ENTER ALPHA -.5 TEST= 2.000000000000000 ANAL= 2.000000000000000 DIFF= 2.220446049250310D-016 ENTER ALPHA The above values are better than the old table due to the increased precision in GLAGU.FOR -.2 TEST= 4.999998821388100 ANAL= 5.000000000000000 DIFF= 1.427392587238790D-006 ENTER ALPHA -.1 TEST= 9.994306877313890 ANAL= 10.000000000000000 DIFF= 0.002717118659016 ENTER ALPHA ENTER ALPHA -.05 TEST= 19.506829422016500 ANAL= 20.000000000000000 DIFF= 0.105475627052240 ENTER ALPHA -.025 TEST= 33.671550728920300 ANAL= 40.000000000000000 DIFF= 0.642007601415472 ENTER ALPHA Very negative value of alpha are also of interest ENTER ALPHA -4 TEST= 0.2499999966161755 ANAL= 0.2500000000000000 DIFF= 5.7768075045760980D-009 ENTER ALPHA -8 TEST= 0.1249529377004137 ANAL= 0.1250000000000000 DIFF= 2.8712992098584020D-005 ENTER ALPHA -16 TEST= 0.0596715658622538 ANAL= 0.0625000000000000 DIFF= 0.0007053403985482 ENTER ALPHA -32 TEST= 0.0189501719947952 ANAL= 0.0312500000000000 DIFF= 0.0012068368532991 ENTER ALPHA -64 TEST= 0.0019825548409274 ANAL= 0.0156250000000000 DIFF= 3.2914875963343910D-004 The good range with 8+ digit accuracy is -4<<-.5 The test function I copied tglagu to tfun.for and made tfun.wpj. The function above is 1 integrated from 2 to = 0.00803884. Write this as 3/ 2 2 x 100 2 1 x 2 100 3/ 2 dx 0.00803884 Let x’=x-2, and multiply by the needed exponential exp x dx 0.00803884 3/ 2 0 exp x 2 x 2 100 TEST= Steve Claims DIFF= (3) (4) 0.0079532072818606 0.00803884 0.0000092540550930986930 0.00008563272 The problem is that 1/x3 is not even close to exponential in its decay. Thus there is more long range part than one would expect. Assume that the form is Decay as exp(-alpha x) exp x exp x 0 x 2 2 100 3/ 2 dx 0.00803884 (5) Note that this is not the same alpha as that in the section #Test alpha. Now let x’=x 1 exp x ' exp x ' dx ' 0.00803884 (6) 3/ 2 0 2 x ' 2 100 With alpha at out disposal. In particular the slow convergence of x-3 implies that we might want alpha in (5) to be on the order of 0.01 or so. This places the points at x/ much further out than before. tfun.for tfun.wpj ENTER A POSITIVE VALUE FOR ALPHA 1 TEST= 0.0079532072818606 Steve Claims 0.00803884 DIFF= 9.2540550930986930D-006 ENTER A POSITIVE VALUE FOR ALPHA .5 TEST= 0.0080166513768168 Steve Claims 0.00803884 DIFF= 2.4569700125334770D-006 ENTER A POSITIVE VALUE FOR ALPHA .25 TEST= 0.0080332038327021 Steve Claims 0.00803884 DIFF= 6.3010351074137270D-007 ENTER A POSITIVE VALUE FOR ALPHA .125 TEST= 0.0080374194522396 Steve Claims 0.00803884 Diff 0.000000149 Actual diff 0.000001420 DIFF= 1.4932011877660800D-007 The estimate with the smallest error ENTER A POSITIVE VALUE FOR ALPHA .0625 TEST= 0.0080373109389459 Steve Claims 0.00803884 DIFF= 7.8236501858258700D-007 ENTER A POSITIVE VALUE FOR ALPHA Further thoughts a 1 s 2 2 3/ 2 1 s2 2 tfun.wpj ENTER A POSITIVE VALUE FOR ALPHA .05 TEST= 0.0080328627579463 3/ 2 ds ds s 2 s2 2 1/ 2 1 2 (7) a 2 a2 2 1/ 2 Steve Claims 0.00803884 Analytic = 0.0080388386486182 DIFF= 1.2883721617444610D-006 By subtracting out the analytic integral, I can get to any desired accuracy. The actual integral of interest is 3 v p 3 ds exp p 2 / s 2 2 Re 1 exp z Rs ', pi w jz Rs ', pi / s '3 / 2 (8) 0 j 1 s ' s2 2 (9) z Rs ' jpx / 2 s ' The exponential of p2/s2 rapidly goes to 1, while the 1-exp()w is plotted in 1-w.htm and also rapidly becomes 1. The 1/s3/2 is analytic for all ranges. Thus from a to infinity 3 3 v a, p ds exp p 2 / s 2 Re 1 exp z Rs, pi w jz Rs, pi 1 / s 3 / 2 a j 1 1 a 3 2 2 2 2 1/ 2 a (10)