Program g05khfe

!     G05KHF Example Program Text

!     Mark 26.1 Release. NAG Copyright 2016.

!     .. Use Statements ..
      Use nag_library, Only: g05kff, g05khf, g05saf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: lseed = 1, nin = 5, nout = 6
!     .. Local Scalars ..
      Integer                          :: genid, i, ifail, lstate, n, nv,      &
                                          subid
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: x(:,:)
      Integer                          :: seed(lseed)
      Integer, Allocatable             :: state(:,:)
!     .. Executable Statements ..
      Write (nout,*) 'G05KHF Example Program Results'
      Write (nout,*)

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

!     Read in the base generator information and seed
      Read (nin,*) genid, subid, seed(1)

!     Read in number of streams and sample size for each stream
      Read (nin,*) n, nv

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

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

      Allocate (x(nv,n))

!     Prepare N streams
      Do i = 1, n
!       Initialize each stream to a repeatable sequence
        ifail = 0
        Call g05kff(genid,subid,seed,lseed,state(1,i),lstate,ifail)

!       Prepare the I'th out of N streams
        ifail = 0
        Call g05khf(n,i,state(1,i),ifail)
      End Do

!     Generate a NV variates, from a uniform distribution, from each stream
      Do i = 1, n
        ifail = 0
        Call g05saf(nv,state(1,i),x(1,i),ifail)
      End Do

!     Display results
      Do i = 1, n
        Write (nout,99998) 'Stream ', i
        Write (nout,99999) x(1:nv,i)
        Write (nout,*)
      End Do

99999 Format (1X,F10.4)
99998 Format (1X,A,I16)
    End Program g05khfe