NAG Library Manual, Mark 27.3
Interfaces:  FL   CL   CPP   AD 

NAG FL Interface Introduction
Example description
!   D01GCF Example Program Text
!   Mark 27.3 Release. NAG Copyright 2021.

    Module d01gcfe_mod

!     D01GCF 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       :: ndim = 4, nout = 6
    Contains
      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)
!       .. Executable Statements ..
        c = 0.0E0_nag_wp
        d = 1.0E0_nag_wp

        Return

      End Subroutine region
      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                      :: cos, real, sum
!       .. Executable Statements ..
        f = cos(0.5E0_nag_wp+2.0E0_nag_wp*sum(x(1:ndim))-real(ndim,kind=nag_wp &
          ))

        Return

      End Function f
    End Module d01gcfe_mod
    Program d01gcfe

!     D01GCF Example Main Program

!     .. Use Statements ..
      Use d01gcfe_mod, Only: f, ndim, nout, region
      Use nag_library, Only: d01gcf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: err, res
      Integer                          :: ifail, itrans, npts, nrand
!     .. Local Arrays ..
      Real (Kind=nag_wp)               :: vk(ndim)
!     .. Executable Statements ..
      Write (nout,*) 'D01GCF Example Program Results'

      npts = 2
      itrans = 0
      nrand = 4

      ifail = 0
      Call d01gcf(ndim,f,region,npts,vk,nrand,itrans,res,err,ifail)

      Write (nout,*)
      Write (nout,99999) 'Result =', res, '  Standard error =', err

99999 Format (1X,A,F13.5,A,E10.2)
    End Program d01gcfe