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

NAG FL Interface Introduction
Example description
    Program g05kgfe

!     G05KGF Example Program Text

!     Mark 27.3 Release. NAG Copyright 2021.

!     .. Use Statements ..
      Use nag_library, Only: g05kgf, g05tlf
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nout = 6
!     .. Local Scalars ..
      Integer                          :: genid, ifail, lstate, n, subid
!     .. Local Arrays ..
      Integer, Allocatable             :: state(:), x1(:), x2(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: any
!     .. Executable Statements ..
      Write (nout,*) 'G05KGF Example Program Results'
      Write (nout,*)

!     Choose the base generator
      genid = 3
      subid = 1

!     Initial call to initializer to get size of STATE array
      lstate = 0
      Allocate (state(lstate))
      ifail = 0
      Call g05kgf(genid,subid,state,lstate,ifail)

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

!     Initialize the generator to a non-repeatable sequence
      ifail = 0
      Call g05kgf(genid,subid,state,lstate,ifail)

!     Using samples of size 500
      n = 500
      Allocate (x1(n),x2(n))

!     Generate a sample of values from a discrete uniform distribution
      Call g05tlf(n,-100,100,state,x1,ifail)

!     Re-initialize the generator to another non-repeatable sequence
!     NB: In practice, in order to preserve its statistical properties,
!     you should only initialize the RNG generators once
      ifail = 0
      Call g05kgf(genid,subid,state,lstate,ifail)

!     Generate a second sample of values from the same distribution
      Call g05tlf(n,-100,100,state,x2,ifail)

!     Check that the two samples are different
      If (any(x1/=x2)) Then
        Write (nout,*) 'The two samples differ, as expected'
      Else
        Write (nout,*) 'The two samples are the same'
        Write (nout,*) 'whilst this is possible, it is unlikely'
      End If

    End Program g05kgfe