! D01RGF Example Program Text ! Mark 24 Release. NAG Copyright 2012. Module d01rgfe_mod ! D01ATF Example Program Module: ! Parameters and User-defined Routines ! .. Use Statements .. Use nag_library, Only: nag_wp ! .. Implicit None Statement .. Implicit None ! .. Parameters .. Integer, Parameter :: nout = 6 Contains Subroutine f(x,nx,fv,iflag,iuser,ruser) ! .. Scalar Arguments .. Integer, Intent (Inout) :: iflag Integer, Intent (In) :: nx ! .. Array Arguments .. Real (Kind=nag_wp), Intent (Out) :: fv(nx) Real (Kind=nag_wp), Intent (Inout) :: ruser(*) Real (Kind=nag_wp), Intent (In) :: x(nx) Integer, Intent (Inout) :: iuser(*) ! .. Intrinsic Procedures .. Intrinsic :: log, sin ! .. Executable Statements .. fv = sin(x)/x*log(10.0_nag_wp*(1.0_nag_wp-x)) Return End Subroutine f End Module d01rgfe_mod Program d01rgfe ! D01RGF Example Main Program ! .. Use Statements .. Use nag_library, Only: d01rgf, nag_wp, x07caf, x07cbf Use d01rgfe_mod, Only: f, nout ! .. Implicit None Statement .. Implicit None ! .. Local Scalars .. Real (Kind=nag_wp) :: a, b, dinest, epsabs, epsrel, & errest Integer :: ifail, nevals ! .. Local Arrays .. Real (Kind=nag_wp) :: ruser(1) Integer :: exmode(3), exmode_old(3), iuser(1) ! .. Executable Statements .. Write (nout,*) 'D01RGF Example Program Results' ! The example function can raise various exceptions - it contains ! a division by zero and a log singularity - although its integral ! is well behaved. ! Save the original halting mode Call x07caf(exmode_old) ! Turn exception halting mode off for the three common exceptions ! overflow, division-by-zero, and invalid operation. exmode = (/0,0,0/) Call x07cbf(exmode) epsabs = 0.0_nag_wp epsrel = 1.0E-04_nag_wp a = -1.0_nag_wp b = 1.0_nag_wp ! Evaluate the integral ifail = -1 Call d01rgf(a,b,f,epsabs,epsrel,dinest,errest,nevals,iuser,ruser,ifail) Write (nout,*) Write (nout,99999) 'A ', 'lower limit of integration', a Write (nout,99999) 'B ', 'upper limit of integration', b Write (nout,99998) 'EPSABS', 'absolute accuracy requested', epsabs Write (nout,99998) 'EPSREL', 'relative accuracy requested', epsrel Write (nout,*) If (ifail>=0) Then Write (nout,99997) 'DINEST', 'approximation to the integral', dinest Write (nout,99998) 'ERREST', 'estimate of the absolute error', errest Write (nout,99996) 'NEVALS', 'number of function evaluations', nevals End If ! Restore the original halting mode Call x07cbf(exmode_old) 99999 Format (1X,A6,' - ',A30,' = ',F10.4) 99998 Format (1X,A6,' - ',A30,' = ',E10.2) 99997 Format (1X,A6,' - ',A30,' = ',F10.5) 99996 Format (1X,A6,' - ',A30,' = ',I10) End Program d01rgfe