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

    Module g05ynfe_mod

!     G05YNF 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                           :: ifun
!     .. Parameters ..
      Integer, Parameter, Public       :: lseed = 1, nin = 5, nout = 6
    Contains
      Function ifun(x,lx)
!       Function being integrated, in this case
!       ABS(4.0 X - 2)

!       .. Function Return Value ..
        Real (Kind=nag_wp)             :: ifun
!       .. Scalar Arguments ..
        Integer, Intent (In)           :: lx
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (In) :: x(lx)
!       .. Local Scalars ..
        Integer                        :: d
!       .. Intrinsic Procedures ..
        Intrinsic                      :: abs
!       .. Executable Statements ..
        ifun = 1.0E0_nag_wp
        Do d = 1, lx
          ifun = ifun*abs(4.0E0_nag_wp*x(d)-2.0E0_nag_wp)
        End Do
      End Function ifun
    End Module g05ynfe_mod
    Program g05ynfe

!     G05YNF Example Main Program

!     .. Use Statements ..
      Use g05ynfe_mod, Only: ifun, lseed, nin, nout
      Use nag_library, Only: g05kff, g05ymf, g05ynf, nag_wp, x04caf
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: sum_nag, vsbl
      Integer                          :: dn, genid, i, idim, ifail, iskip,    &
                                          ldquas, liref, lstate, n, nsdigi,    &
                                          pgenid, psubid, rcord, stype
      Character (80)                   :: title
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: quas(:,:)
      Integer, Allocatable             :: iref(:), state(:)
      Integer                          :: seed(lseed)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: real
!     .. Executable Statements ..
      Write (nout,*) 'G05YNF Example Program Results'
      Write (nout,*)

!     Skip heading in data file
      Read (nin,*)

!     Read in the base generator information and seed
      Read (nin,*) pgenid, psubid, seed(1)

!     Initial call to initializer to get size of STATE array
      lstate = 0
      Allocate (state(lstate))
      ifail = 0
      Call g05kff(pgenid,psubid,seed,lseed,state,lstate,ifail)

!     Reallocate STATE
      Deallocate (state)
      Allocate (state(lstate))

!     Initialize the generator to a repeatable sequence
      ifail = 0
      Call g05kff(pgenid,psubid,seed,lseed,state,lstate,ifail)

!     Fix the RCORD = 1, so QUAS(IDIM,N). As we
!     are accessing each dimension in turn for a given variate
!     when evaluating the function, this is more efficient
      rcord = 1

!     Read in quasi-random generator and scrambling to use
      Read (nin,*) genid, stype, nsdigi

!     Read in problem size
      Read (nin,*) n, idim, iskip

      If (genid==4) Then
        liref = 407
      Else
        liref = 32*idim + 7
      End If
      ldquas = idim
      Allocate (quas(ldquas,n),iref(liref))

!     Call the initializer for the quasi-random sequence
      ifail = 0
      Call g05ynf(genid,stype,idim,iref,liref,iskip,nsdigi,state,ifail)

!     Generate N quasi-random variates
      ifail = 0
      Call g05ymf(n,rcord,quas,ldquas,iref,ifail)

!     Evaluate the function, and sum
      sum_nag = 0.0E0_nag_wp
      Do i = 1, n
        sum_nag = sum_nag + ifun(quas(1:idim,i),idim)
      End Do

!     Convert sum to mean value
      vsbl = sum_nag/real(n,kind=nag_wp)
      Write (nout,99999)
      Write (nout,99999) 'Value of integral = ', vsbl

!     Read in number of variates to display
      Read (nin,*) dn

!     Display the first DN variates
      Write (nout,*)
      Write (title,99998) 'First ', dn, ' variates for all ', idim,            &
        ' dimensions'
      Flush (nout)
      ifail = 0
      Call x04caf('General',' ',idim,dn,quas,ldquas,title,ifail)

99999 Format (1X,A,F8.4)
99998 Format (A,I0,A,I0,A)
    End Program g05ynfe