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

    Module d01gdfe_mod

!     D01GDF 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                           :: vecfun, vecreg
!     .. Parameters ..
      Integer, Parameter, Public       :: ndim = 4, nout = 6
    Contains
      Subroutine vecfun(ndim,x,fv,m)

!       .. Scalar Arguments ..
        Integer, Intent (In)           :: m, ndim
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Out) :: fv(m)
        Real (Kind=nag_wp), Intent (In) :: x(m,ndim)
!       .. Local Scalars ..
        Integer                        :: i
!       .. Intrinsic Procedures ..
        Intrinsic                      :: cos, real, sum
!       .. Executable Statements ..
        Do i = 1, m
          fv(i) = cos(0.5E0_nag_wp+2.0E0_nag_wp*sum(x(i,                       &
            1:ndim))-real(ndim,kind=nag_wp))
        End Do

        Return

      End Subroutine vecfun
      Subroutine vecreg(ndim,x,j,c,d,m)

!       .. Scalar Arguments ..
        Integer, Intent (In)           :: j, m, ndim
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Out) :: c(m), d(m)
        Real (Kind=nag_wp), Intent (In) :: x(m,ndim)
!       .. Executable Statements ..
        c(1:m) = 0.0E0_nag_wp
        d(1:m) = 1.0E0_nag_wp

        Return

      End Subroutine vecreg
    End Module d01gdfe_mod
    Program d01gdfe

!     D01GDF Example Main Program

!     .. Use Statements ..
      Use d01gdfe_mod, Only: ndim, nout, vecfun, vecreg
      Use nag_library, Only: d01gdf, 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,*) 'D01GDF Example Program Results'

      npts = 2
      itrans = 0
      nrand = 4

      ifail = 0
      Call d01gdf(ndim,vecfun,vecreg,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 d01gdfe