Example description
!   E01TNF Example Program Text
!   Mark 26.2 Release. NAG Copyright 2017.

    Module e01tnfe_mod

!     E01TNF Example Program Module:
!            Parameters and User-defined Routines

!     .. Use Statements ..
      Use nag_library, Only: nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Accessibility Statements ..
      Private
      Public                           :: funct
!     .. Parameters ..
      Real (Kind=nag_wp), Parameter    :: one = 1.0_nag_wp
      Real (Kind=nag_wp), Parameter    :: six = 6.0_nag_wp
      Real (Kind=nag_wp), Parameter    :: three = 3.0_nag_wp
      Integer, Parameter, Public       :: nin = 5, nout = 6
    Contains
      Function funct(x)
!       This function evaluates the 5D function funct.

!       .. Function Return Value ..
        Real (Kind=nag_wp)             :: funct
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (In) :: x(5)
!       .. Intrinsic Procedures ..
        Intrinsic                      :: cos
!       .. Executable Statements ..
        funct = ((1.25_nag_wp+cos(5.4_nag_wp*x(5)))*cos(six*x(1))*cos(six*x(2) &
          )*cos(six*x(3)))/(six+six*(three*x(4)-one)**2)

        Return
      End Function funct
    End Module e01tnfe_mod
    Program e01tnfe

!     E01TNF Example Main Program

!     .. Use Statements ..
      Use e01tnfe_mod, Only: funct, nin, nout
      Use nag_library, Only: e01tmf, e01tnf, g05kff, g05saf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: lseed = 1
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: fun
      Integer                          :: genid, i, ifail, liq, lrq, lstate,   &
                                          m, n, nq, nw, subid
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: f(:), q(:), qx(:,:), rq(:), x(:,:),  &
                                          xe(:,:)
      Integer, Allocatable             :: iq(:), state(:)
      Integer                          :: seed(lseed), seed2(lseed)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: abs
!     .. Executable Statements ..
      Write (nout,*) 'E01TNF Example Program Results'

!     Skip heading in data file
      Read (nin,*)

!     Read in the base generator information and seeds
      Read (nin,*) genid, subid, seed(1), seed2(1)

!     Initial call to initializer to get size of STATE array
      lstate = 0
      Allocate (state(lstate))
      ifail = 0
      Call g05kff(genid,subid,seed,lseed,state,lstate,ifail)

!     Reallocate STATE
      Deallocate (state)
      Allocate (state(lstate))

!     Initialize the generator to a repeatable sequence
      ifail = 0
      Call g05kff(genid,subid,seed,lseed,state,lstate,ifail)

!     Input the number of nodes.
      Read (nin,*) m
      liq = 2*m + 1
      lrq = 21*m + 11
      Allocate (x(5,m),f(m),iq(liq),rq(lrq))

!     Generate the data points X
      ifail = 0
      Call g05saf(5*m,state,x,ifail)

!     Evaluate F
      Do i = 1, m
        f(i) = funct(x(1,i))
      End Do

!     Generate the interpolant using E01TMF.
      nq = 0
      nw = 0

      ifail = 0
      Call e01tmf(m,x,f,nw,nq,iq,rq,ifail)

!     Input the number of evaluation points.
      Read (nin,*) n
      Allocate (xe(5,n),q(n),qx(5,n))

!     Generate repeatable evaluation points.
      ifail = 0
      Call g05kff(genid,subid,seed2,lseed,state,lstate,ifail)
      ifail = 0
      Call g05saf(5*n,state,xe,ifail)

!     Evaluate the interpolant.
      ifail = 0
      Call e01tnf(m,x,f,iq,rq,n,xe,q,qx,ifail)

      Write (nout,99997)
      Write (nout,99998)
      Do i = 1, n
        fun = funct(xe(1,i))
        Write (nout,99999) i, fun, q(i), abs(fun-q(i))
      End Do

99999 Format (1X,I4,1X,3F10.4)
99998 Format (4X,'---|',20('-'),'+',15('-'))
99997 Format (/,4X,'I  |',2X,'F(I)',6X,'Q(I)',4X,'|',1X,'|F(I)-Q(I)|')
    End Program e01tnfe