! D02NCF Example Program Text ! Mark 24 Release. NAG Copyright 2012. Module d02ncfe_mod ! D02NCF Example Program Module: ! Parameters and User-defined Routines ! .. Use Statements .. Use nag_library, Only: nag_wp ! .. Implicit None Statement .. Implicit None ! .. Parameters .. Real (Kind=nag_wp), Parameter :: alpha = 0.04_nag_wp Real (Kind=nag_wp), Parameter :: beta = 1.0E4_nag_wp Real (Kind=nag_wp), Parameter :: gamma = 3.0E7_nag_wp Real (Kind=nag_wp), Parameter :: one = 1.0_nag_wp Real (Kind=nag_wp), Parameter :: two = 2.0_nag_wp Integer, Parameter :: iset = 1, itrace = 0, ml = 1, & mu = 2, neq = 3, nin = 5 Integer, Parameter :: njcpvt = neq Integer, Parameter :: nout = 6 Integer, Parameter :: nrw = 50 + 4*neq Integer, Parameter :: nwkjac = neq*(2*ml+mu+1) Integer, Parameter :: ldysav = neq Contains Subroutine fcn(neq,t,y,f,ires) ! .. Scalar Arguments .. Real (Kind=nag_wp), Intent (In) :: t Integer, Intent (Inout) :: ires Integer, Intent (In) :: neq ! .. Array Arguments .. Real (Kind=nag_wp), Intent (Out) :: f(neq) Real (Kind=nag_wp), Intent (In) :: y(neq) ! .. Executable Statements .. f(1) = -alpha*y(1) + beta*y(2)*y(3) f(2) = alpha*y(1) - beta*y(2)*y(3) - gamma*y(2)*y(2) f(3) = gamma*y(2)*y(2) Return End Subroutine fcn Subroutine jac(neq,t,y,h,d,ml,mu,p) ! .. Scalar Arguments .. Real (Kind=nag_wp), Intent (In) :: d, h, t Integer, Intent (In) :: ml, mu, neq ! .. Array Arguments .. Real (Kind=nag_wp), Intent (Inout) :: p(ml+mu+1,neq) Real (Kind=nag_wp), Intent (In) :: y(neq) ! .. Local Scalars .. Real (Kind=nag_wp) :: hxd ! .. Executable Statements .. hxd = h*d p(1,1) = one - hxd*(-alpha) p(2,1) = -hxd*(beta*y(3)) p(3,1) = -hxd*(beta*y(2)) p(1,2) = -hxd*(alpha) p(2,2) = one - hxd*(-beta*y(3)-two*gamma*y(2)) p(3,2) = -hxd*(-beta*y(2)) p(1,3) = -hxd*(two*gamma*y(2)) p(2,3) = one - hxd*(0.0_nag_wp) Return End Subroutine jac End Module d02ncfe_mod Program d02ncfe ! D02NCF Example Main Program ! .. Use Statements .. Use nag_library, Only: d02nby, d02ncf, d02ntf, d02nwf, d02nyf, d02nzf, & nag_wp, x04abf Use d02ncfe_mod, Only: fcn, iset, itrace, jac, ldysav, ml, mu, neq, nin, & njcpvt, nout, nrw, nwkjac ! .. Implicit None Statement .. Implicit None ! .. Local Scalars .. Real (Kind=nag_wp) :: h, h0, hmax, hmin, hu, t, tcrit, & tcur, tolsf, tout Integer :: i, ifail, imxer, itask, itol, & maxord, maxstp, mxhnil, niter, & nje, nq, nqu, nre, nst, outchn, & sdysav ! .. Local Arrays .. Real (Kind=nag_wp), Allocatable :: atol(:), rtol(:), rwork(:), & wkjac(:), y(:), ydot(:), ysav(:,:) Real (Kind=nag_wp) :: con(6) Integer :: inform(23) Integer, Allocatable :: jacpvt(:) Logical, Allocatable :: algequ(:) ! .. Executable Statements .. Write (nout,*) 'D02NCF Example Program Results' ! Skip heading in data file Read (nin,*) Read (nin,*) maxord, maxstp, mxhnil sdysav = maxord + 3 Allocate (atol(neq),rtol(neq),rwork(nrw),wkjac(nwkjac),y(neq),ydot(neq), & ysav(ldysav,sdysav),jacpvt(njcpvt),algequ(neq)) outchn = nout Call x04abf(iset,outchn) ! Integrate to tout (itask=1 i.e. overshooting and internal interpolation) ! using the blend method. Default values for the array con are used. ! Employ scalar relative tolerance and vector absolute tolerance. ! The Jacobian is evaluated by jac. ! monitr subroutine replaced by NAG dummy routine D02NBY. Read (nin,*) hmin, hmax, h0, tcrit Read (nin,*) t, tout Read (nin,*) itol Read (nin,*) y(1:neq) Read (nin,*) rtol(1) Read (nin,*) atol(1:neq) con(1:6) = 0.0_nag_wp itask = 1 ! ifail: behaviour on error exit ! =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft ifail = 0 Call d02nwf(neq,sdysav,maxord,con,tcrit,hmin,hmax,h0,maxstp,mxhnil, & 'Average-L2',rwork,ifail) ifail = 0 Call d02ntf(neq,neq,'Analytical',ml,mu,nwkjac,njcpvt,rwork,ifail) Write (nout,99993)(i,i=1,neq) Write (nout,99999) t, (y(i),i=1,neq) ! Soft fail and error messages only ifail = -1 Call d02ncf(neq,ldysav,t,tout,y,ydot,rwork,rtol,atol,itol,inform,fcn, & ysav,sdysav,jac,wkjac,nwkjac,jacpvt,njcpvt,d02nby,itask,itrace,ifail) If (ifail==0) Then Write (nout,99999) t, (y(i),i=1,neq) Else Write (nout,*) Write (nout,99998) 'Exit D02NCF with IFAIL = ', ifail, ' and T = ', t End If ! Reset tout and call D02NZF to override internal choice for stepsize. ! No changes to other parameters. h = 0.7_nag_wp ifail = 0 Call d02nzf(neq,tcrit,h,hmin,hmax,maxstp,mxhnil,rwork,ifail) tout = 10.0_nag_wp ifail = -1 Call d02ncf(neq,ldysav,t,tout,y,ydot,rwork,rtol,atol,itol,inform,fcn, & ysav,sdysav,jac,wkjac,nwkjac,jacpvt,njcpvt,d02nby,itask,itrace,ifail) If (ifail==0) Then Write (nout,99999) t, (y(i),i=1,neq) ifail = 0 Call d02nyf(neq,neq,hu,h,tcur,tolsf,rwork,nst,nre,nje,nqu,nq,niter, & imxer,algequ,inform,ifail) Write (nout,*) Write (nout,99997) hu, h, tcur Write (nout,99996) nst, nre, nje Write (nout,99995) nqu, nq, niter Write (nout,99994) ' Max Err Comp = ', imxer Write (nout,*) Else Write (nout,*) Write (nout,99998) 'Exit D02NCF with IFAIL = ', ifail, ' and T = ', t End If 99999 Format (1X,F8.3,3(F13.5,2X)) 99998 Format (1X,A,I2,A,E12.5) 99997 Format (1X,' HUSED = ',E12.5,' HNEXT = ',E12.5,' TCUR = ',E12.5) 99996 Format (1X,' NST = ',I6,' NRE = ',I6,' NJE = ',I6) 99995 Format (1X,' NQU = ',I6,' NQ = ',I6,' NITER = ',I6) 99994 Format (1X,A,I4) 99993 Format (/1X,' X ',3(' Y(',I1,') ')) End Program d02ncfe