Example description
!   C05AY_P0W_F Example Program Text
!   Mark 27.1 Release. NAG Copyright 2020.
    Module c05ay_p0w_fe_mod

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

!     .. 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       :: nin = 5, nout = 6
    Contains
      Subroutine f(ad_handle,x,z,iuser,ruser)

!       .. Scalar Arguments ..
        Type (c_ptr), Intent (Inout)   :: ad_handle
        Real (Kind=nag_wp), Intent (In) :: x
        Real (Kind=nag_wp), Intent (Out) :: z
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Inout) :: ruser(*)
        Integer, Intent (Inout)        :: iuser(*)
!       .. Executable Statements ..
        z = Exp(-x) - x*ruser(1)
        Return

      End Subroutine f
    End Module c05ay_p0w_fe_mod

    Program c05ay_p0w_fe
!     C05AY_P0W_F Example Main Program

!     .. Use Statements ..
      Use c05ay_p0w_fe_mod, Only: f, nin, nout
      Use iso_c_binding, Only: c_ptr
      Use nagad_library, Only: c05ay_p0w_f
      Use nag_library, Only: nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Type (c_ptr)                     :: ad_handle
      Real (Kind=nag_wp)               :: a, b, eps, eta, x
      Integer                          :: ifail
!     .. Local Arrays ..
      Real (Kind=nag_wp)               :: ruser(1)
      Integer                          :: iuser(1)
!     .. Executable Statements ..

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

!     Skip first line of data file
      Read (nin,*)
!     Read problem parameters
      Read (nin,*) a
      Read (nin,*) b
      Read (nin,*) eps
      Read (nin,*) eta
      Read (nin,*) ruser(1)

!     Call p0w routine
      ifail = 0
      Call c05ay_p0w_f(ad_handle,a,b,eps,eta,f,x,iuser,ruser,ifail)

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

    End Program c05ay_p0w_fe