Example description
!   D01DAF Example Program Text
!   Mark 27.1 Release. NAG Copyright 2020.

    Module d01dafe_mod

!     D01DAF 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                           :: fa, fb, phi1, phi2a, phi2b
!     .. Parameters ..
      Integer, Parameter, Public       :: nout = 6
    Contains
      Function phi1(y)

!       .. Function Return Value ..
        Real (Kind=nag_wp)             :: phi1
!       .. Scalar Arguments ..
        Real (Kind=nag_wp), Intent (In) :: y
!       .. Executable Statements ..
        phi1 = 0.0E0_nag_wp

        Return

      End Function phi1
      Function phi2a(y)

!       .. Function Return Value ..
        Real (Kind=nag_wp)             :: phi2a
!       .. Scalar Arguments ..
        Real (Kind=nag_wp), Intent (In) :: y
!       .. Intrinsic Procedures ..
        Intrinsic                      :: sqrt
!       .. Executable Statements ..
        phi2a = sqrt(1.0E0_nag_wp-y*y)

        Return

      End Function phi2a
      Function fa(x,y)

!       .. Function Return Value ..
        Real (Kind=nag_wp)             :: fa
!       .. Scalar Arguments ..
        Real (Kind=nag_wp), Intent (In) :: x, y
!       .. Executable Statements ..
        fa = x + y

        Return

      End Function fa
      Function phi2b(y)

!       .. Use Statements ..
        Use nag_library, Only: x01aaf
!       .. Function Return Value ..
        Real (Kind=nag_wp)             :: phi2b
!       .. Scalar Arguments ..
        Real (Kind=nag_wp), Intent (In) :: y
!       .. Executable Statements ..
        phi2b = 0.5E0_nag_wp*x01aaf(y)

        Return

      End Function phi2b
      Function fb(x,y)

!       .. Function Return Value ..
        Real (Kind=nag_wp)             :: fb
!       .. Scalar Arguments ..
        Real (Kind=nag_wp), Intent (In) :: x, y
!       .. Intrinsic Procedures ..
        Intrinsic                      :: cos, sin
!       .. Executable Statements ..
        fb = y*y*(cos(x)+sin(x))

        Return

      End Function fb
    End Module d01dafe_mod
    Program d01dafe

!     D01DAF Example Main Program

!     .. Use Statements ..
      Use d01dafe_mod, Only: fa, fb, nout, phi1, phi2a, phi2b
      Use nag_library, Only: d01daf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: absacc, ans, ya, yb
      Integer                          :: ifail, npts
!     .. Executable Statements ..
      Write (nout,*) 'D01DAF Example Program Results'

      ya = 0.0E0_nag_wp
      yb = 1.0E0_nag_wp
      absacc = 1.0E-6_nag_wp

      ifail = 0
      Call d01daf(ya,yb,phi1,phi2a,fa,absacc,ans,npts,ifail)

      Write (nout,*)
      Write (nout,*) 'First formulation'
      Write (nout,99999) 'Integral =', ans
      Write (nout,99998) 'Number of function evaluations =', npts

      ifail = 0
      Call d01daf(ya,yb,phi1,phi2b,fb,absacc,ans,npts,ifail)

      Write (nout,*)
      Write (nout,*) 'Second formulation'
      Write (nout,99999) 'Integral =', ans
      Write (nout,99998) 'Number of function evaluations =', npts

99999 Format (1X,A,F9.4)
99998 Format (1X,A,I5)
    End Program d01dafe