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

    Module d01fdfe_mod

!     D01FDF 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                           :: f, region
!     .. Parameters ..
      Integer, Parameter, Public       :: nout = 6
    Contains
      Function f(ndim,x)

!       .. Function Return Value ..
        Real (Kind=nag_wp)             :: f
!       .. Scalar Arguments ..
        Integer, Intent (In)           :: ndim
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (In) :: x(ndim)
!       .. Intrinsic Procedures ..
        Intrinsic                      :: abs, sqrt, sum
!       .. Executable Statements ..
        f = 1.0E0_nag_wp/sqrt(abs(2.25E0_nag_wp-sum(x(1:ndim)**2)))

        Return

      End Function f
      Subroutine region(ndim,x,j,c,d)

!       .. Scalar Arguments ..
        Real (Kind=nag_wp), Intent (Out) :: c, d
        Integer, Intent (In)           :: j, ndim
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (In) :: x(ndim)
!       .. Intrinsic Procedures ..
        Intrinsic                      :: abs, sqrt, sum
!       .. Executable Statements ..
        If (j>1) Then
          d = sqrt(abs(2.25E0_nag_wp-sum(x(1:(j-1))**2)))
          c = -d
        Else
          c = -1.5E0_nag_wp
          d = 1.5E0_nag_wp
        End If

        Return

      End Subroutine region
    End Module d01fdfe_mod
    Program d01fdfe

!     D01FDF Example Main Program

!     .. Use Statements ..
      Use d01fdfe_mod, Only: f, nout, region
      Use nag_library, Only: d01fdf, d01fdv, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: r0, result, sigma, u
      Integer                          :: ifail, limit, ncalls, ndim
!     .. Executable Statements ..
      Write (nout,*) 'D01FDF Example Program Results'

      ndim = 3
      limit = 8000
      u = 1.5E0_nag_wp
      sigma = 1.5E0_nag_wp
      r0 = 0.9E0_nag_wp

      ifail = 0
      Call d01fdf(ndim,f,sigma,d01fdv,limit,r0,u,result,ncalls,ifail)

      Write (nout,*)
      Write (nout,*) 'Sphere-to-sphere transformation'
      Write (nout,*)
      Write (nout,99999) 'Estimated value of the integral = ', result
      Write (nout,99998) 'Number of integrand evaluations = ', ncalls
      Write (nout,*)
      Write (nout,*) 'Product region transformation'

      sigma = -1.0E0_nag_wp
      r0 = 0.8E0_nag_wp

      ifail = 0
      Call d01fdf(ndim,f,sigma,region,limit,r0,u,result,ncalls,ifail)

      Write (nout,*)
      Write (nout,99999) 'Estimated value of the integral = ', result
      Write (nout,99998) 'Number of integrand evaluations = ', ncalls

99999 Format (1X,A,F9.3)
99998 Format (1X,A,I5)
    End Program d01fdfe