!   D02EJF Example Program Text
!   Mark 23 Release. NAG Copyright 2011.

    MODULE d02ejfe_mod

!      Data for D02EJF example program

!      .. 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       :: zero = 0.0_nag_wp
       INTEGER, PARAMETER                  :: n = 3, nin = 5, nout = 6
!      .. Local Scalars ..
       REAL (KIND=nag_wp)                  :: h, xend
       INTEGER, SAVE                       :: k
    CONTAINS
       SUBROUTINE fcn(x,y,f)

!         .. Implicit None Statement ..
          IMPLICIT NONE
!         .. Scalar Arguments ..
          REAL (KIND=nag_wp), INTENT (IN)     :: x
!         .. Array Arguments ..
          REAL (KIND=nag_wp), INTENT (OUT)    :: f(*)
          REAL (KIND=nag_wp), INTENT (IN)     :: y(*)
!         .. 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 pederv(x,y,pw)

!         .. Implicit None Statement ..
          IMPLICIT NONE
!         .. Scalar Arguments ..
          REAL (KIND=nag_wp), INTENT (IN)     :: x
!         .. Array Arguments ..
          REAL (KIND=nag_wp), INTENT (OUT)    :: pw(*)
          REAL (KIND=nag_wp), INTENT (IN)     :: y(*)
!         .. Executable Statements ..
          pw(1) = -alpha
          pw(2) = alpha
          pw(3) = zero
          pw(4) = beta*y(3)
          pw(5) = -beta*y(3) - 2.0_nag_wp*gamma*y(2)
          pw(6) = 2.0_nag_wp*gamma*y(2)
          pw(7) = beta*y(2)
          pw(8) = -beta*y(2)
          pw(9) = zero
          RETURN
       END SUBROUTINE pederv
       FUNCTION g(x,y)

!         .. Implicit None Statement ..
          IMPLICIT NONE
!         .. Function Return Value ..
          REAL (KIND=nag_wp)                  :: g
!         .. Scalar Arguments ..
          REAL (KIND=nag_wp), INTENT (IN)     :: x
!         .. Array Arguments ..
          REAL (KIND=nag_wp), INTENT (IN)     :: y(*)
!         .. Executable Statements ..
          g = y(1) - 0.9E0_nag_wp
          RETURN
       END FUNCTION g
       SUBROUTINE output(xsol,y)

!         .. Implicit None Statement ..
          IMPLICIT NONE
!         .. Scalar Arguments ..
          REAL (KIND=nag_wp), INTENT (INOUT)  :: xsol
!         .. Array Arguments ..
          REAL (KIND=nag_wp), INTENT (IN)     :: y(*)
!         .. Local Scalars ..
          INTEGER                             :: j
!         .. Intrinsic Functions ..
          INTRINSIC                              real
!         .. Executable Statements ..
          WRITE (nout,99999) xsol, (y(j),j=1,n)
          xsol = xend - real(k,kind=nag_wp)*h
          k = k - 1
          RETURN

99999     FORMAT (1X,F8.2,3F13.5)
       END SUBROUTINE output
    END MODULE d02ejfe_mod
    PROGRAM d02ejfe

!      D02EJF Example Main Program

!      .. Use Statements ..
       USE nag_library, ONLY : d02ejf, d02ejw, d02ejx, d02ejy, nag_wp
       USE d02ejfe_mod, ONLY : fcn, g, h, k, n, nin, nout, output, pederv, xend
!      .. Implicit None Statement ..
       IMPLICIT NONE
!      .. Local Scalars ..
       REAL (KIND=nag_wp)                  :: tol, x, xinit
       INTEGER                             :: i, icase, ifail, iw, j, kinit
!      .. Local Arrays ..
       REAL (KIND=nag_wp), ALLOCATABLE     :: w(:), y(:), yinit(:)
!      .. Intrinsic Functions ..
       INTRINSIC                              real
!      .. Executable Statements ..
       WRITE (nout,*) 'D02EJF Example Program Results'
       iw = (12+n)*n + 50
       ALLOCATE (w(iw),y(n),yinit(n))
!      Skip heading in data file
       READ (nin,*)
!      xinit: initial x value, xend: final x value
!      y: initial solution values
       READ (nin,*) xinit, xend
       READ (nin,*) yinit(1:n)
       READ (nin,*) kinit
       DO icase = 1, 5
          IF (icase/=2) THEN
             WRITE (nout,99995) icase, 'Jacobian internally'
          ELSE
             WRITE (nout,99995) icase, 'Jacobian by PEDERV'
          END IF
          SELECT CASE (icase)
          CASE (1,2)
             WRITE (nout,99994) 'intermediate output, root-finding'
          CASE (3)
             WRITE (nout,99994) 'no intermediate output, root-finding'
          CASE (4)
             WRITE (nout,99994) 'intermediate output, no root-finding'
          CASE (5)
             WRITE (nout,99994) &
                'no intermediate output, no root-finding (integrate to XEND)'
          END SELECT
          DO j = 3, 4
             tol = 10.0E0_nag_wp**(-j)
             WRITE (nout,99999) ' Calculation with TOL =', tol
             x = xinit
             y(1:n) = yinit(1:n)
             IF (icase/=3) THEN
                WRITE (nout,*) '     X         Y(1)         Y(2)         Y(3)'
                k = kinit
                h = (xend-x)/real(k+1,kind=nag_wp)
             END IF
             ifail = 0
             SELECT CASE (icase)
             CASE (1)
                CALL d02ejf(x,xend,n,y,fcn,d02ejy,tol,'Default',output,g,w,iw, &
                   ifail)
                WRITE (nout,99998) '  Root of Y(1)-0.9 at', x
                WRITE (nout,99997) '  Solution is', (y(i),i=1,n)
             CASE (2)
                CALL d02ejf(x,xend,n,y,fcn,pederv,tol,'Default',output,g,w,iw, &
                   ifail)
                WRITE (nout,99998) '  Root of Y(1)-0.9 at', x
                WRITE (nout,99997) '  Solution is', (y(i),i=1,n)
             CASE (3)
                CALL d02ejf(x,xend,n,y,fcn,d02ejy,tol,'Default',d02ejx,g,w,iw, &
                   ifail)
                WRITE (nout,99998) '  Root of Y(1)-0.9 at', x
                WRITE (nout,99997) '  Solution is', (y(i),i=1,n)
             CASE (4)
                ifail = 0
                CALL d02ejf(x,xend,n,y,fcn,d02ejy,tol,'Default',output,d02ejw, &
                   w,iw,ifail)
             CASE (5)
                WRITE (nout,99996) x, (y(i),i=1,n)
                CALL d02ejf(x,xend,n,y,fcn,d02ejy,tol,'Default',d02ejx,d02ejw, &
                   w,iw,ifail)
                WRITE (nout,99996) x, (y(i),i=1,n)
             END SELECT
             IF (tol<0.0E0_nag_wp) WRITE (nout,*) '  Range too short for TOL'
          END DO
          IF (icase<5) THEN
             WRITE (nout,*)
          END IF
       END DO

99999  FORMAT (/1X,A,E8.1)
99998  FORMAT (1X,A,F7.3)
99997  FORMAT (1X,A,3F13.5)
99996  FORMAT (1X,F8.2,3F13.5)
99995  FORMAT (/1X,'Case ',I1,': calculating ',A,',')
99994  FORMAT (8X,A)
    END PROGRAM d02ejfe