Example description
!   D01FC_P0W_F Example Program Text
!   Mark 27 Release. NAG Copyright 2019.

    Module d01fc_p0w_fe_mod

!     .. Use Statements ..
      Use iso_c_binding, Only: c_ptr
      Use nag_library, Only: nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Accessibility Statements ..
      Private
      Public                           :: f
!     .. Parameters ..
      Integer, Parameter, Public       :: ndim = 4, nout = 6
      Integer, Parameter, Public       :: maxpts = 1000*ndim
      Integer, Parameter, Public       :: lenwrk = (ndim+2)*(1+maxpts/(2**ndim &
                                          +2*ndim*ndim+2*ndim+1))
    Contains
      Subroutine f(ad_handle,ndim,z,fz,iuser,ruser)

!       .. Scalar Arguments ..
        Type (c_ptr), Intent (Inout)   :: ad_handle
        Real (Kind=nag_wp), Intent (Out) :: fz
        Integer, Intent (In)           :: ndim
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Inout) :: ruser(*)
        Real (Kind=nag_wp), Intent (In) :: z(ndim)
        Integer, Intent (Inout)        :: iuser(*)
!       .. Local Scalars ..
        Real (Kind=nag_wp)             :: f1, f2, f3
!       .. Intrinsic Procedures ..
        Intrinsic                      :: exp
!       .. Executable Statements ..
        f1 = ruser(1)*z(1)*z(3)*z(3)
        f2 = ruser(2)*z(1)*z(3)
        f2 = exp(f2)
        f3 = ruser(3) + z(2) + z(4)
        f3 = f3*f3
        fz = f1*f2/f3
        Return

      End Subroutine f
    End Module d01fc_p0w_fe_mod

    Program d01fc_p0w_fe
!     D01FC_P0W_F Example Main Program

!     .. Use Statements ..
      Use d01fc_p0w_fe_mod, Only: f, lenwrk, maxpts, ndim, nout
      Use iso_c_binding, Only: c_ptr
      Use nagad_library, Only: d01fc_p0w_f
      Use nag_library, Only: nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Type (c_ptr)                     :: ad_handle
      Real (Kind=nag_wp)               :: acc, eps, finval
      Integer                          :: ifail, minpts
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: a(:), b(:), work(:)
      Real (Kind=nag_wp)               :: ruser(3)
      Integer                          :: iuser(1)
!     .. Executable Statements ..

      Write (nout,*) 'D01FC_P0W_F Example Program Results'

      Allocate (a(ndim),b(ndim),work(lenwrk))

      a(1:ndim) = 0.0E0_nag_wp
      b(1:ndim) = 1.0E0_nag_wp
      eps = 0.0001E0_nag_wp
      minpts = 0
      ruser(1) = 4.0_nag_wp
      ruser(2) = 2.0_nag_wp
      ruser(3) = 1.0_nag_wp

!     Call the passive routine
      ifail = 0
      Call d01fc_p0w_f(ad_handle,ndim,a,b,minpts,maxpts,f,eps,acc,lenwrk,work, &
        finval,iuser,ruser,ifail)

      Write (nout,99999) ' Solution, x =', finval
99999 Format (1X,A,1X,F12.5)

    End Program d01fc_p0w_fe