!   D01ANF Example Program Text
!   Mark 26.1 Release. NAG Copyright 2016.

    Module d01anfe_mod

!     D01ANF 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                           :: g
!     .. Parameters ..
      Integer, Parameter, Public       :: lw = 800, nout = 6
      Integer, Parameter, Public       :: liw = lw/2
    Contains
      Function g(x)

!       .. Function Return Value ..
        Real (Kind=nag_wp)             :: g
!       .. Scalar Arguments ..
        Real (Kind=nag_wp), Intent (In) :: x
!       .. Intrinsic Procedures ..
        Intrinsic                      :: log
!       .. Executable Statements ..
        If (x>0.0E0_nag_wp) Then
          g = log(x)
        Else
          g = 0.0E0_nag_wp
        End If

        Return

      End Function g
    End Module d01anfe_mod
    Program d01anfe

!     D01ANF Example Main Program

!     .. Use Statements ..
      Use d01anfe_mod, Only: g, liw, lw, nout
      Use nag_library, Only: d01anf, nag_wp, x01aaf
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: a, abserr, b, epsabs, epsrel, omega, &
                                          pi, result
      Integer                          :: ifail, key
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: w(:)
      Integer, Allocatable             :: iw(:)
!     .. Executable Statements ..
      Write (nout,*) 'D01ANF Example Program Results'

      Allocate (w(lw),iw(liw))

      epsrel = 1.0E-04_nag_wp
      epsabs = 0.0E+00_nag_wp
      a = 0.0E0_nag_wp
      b = 1.0E0_nag_wp
      omega = 10.0E0_nag_wp*x01aaf(pi)
      key = 2

      ifail = -1
      Call d01anf(g,a,b,omega,key,epsabs,epsrel,result,abserr,w,lw,iw,liw,     &
        ifail)

      If (ifail>=0) Then
        Write (nout,*)
        Write (nout,99999) 'A     ', 'lower limit of integration', a
        Write (nout,99999) 'B     ', 'upper limit of integration', b
        Write (nout,99998) 'EPSABS', 'absolute accuracy requested', epsabs
        Write (nout,99998) 'EPSREL', 'relative accuracy requested', epsrel
      End If

      If (ifail>=0 .And. ifail<=5) Then
        Write (nout,*)
        Write (nout,99997) 'RESULT', 'approximation to the integral', result
        Write (nout,99998) 'ABSERR', 'estimate of the absolute error', abserr
        Write (nout,99996) 'IW(1) ', 'number of subintervals used', iw(1)
      End If

99999 Format (1X,A6,' - ',A32,' = ',F10.4)
99998 Format (1X,A6,' - ',A32,' = ',E9.2)
99997 Format (1X,A6,' - ',A32,' = ',F9.5)
99996 Format (1X,A6,' - ',A32,' = ',I4)
    End Program d01anfe