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

NAG FL Interface Introduction
Example description
    Program g05yrfe

!     G05YRF Example Main Program

!     Mark 29.3 Release. NAG Copyright 2023.

!     .. Use Statements ..
      Use nag_library, Only: g05ylf, g05yrf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Integer                          :: dn, fdim, genid, i, idim, ifail,     &
                                          iskip, ldim, ldquas, liref, n, rdim, &
                                          sorder
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: quas(:,:), std(:), xmean(:)
      Integer, Allocatable             :: iref(:)
!     .. Executable Statements ..
      Write (nout,*) 'G05YRF Example Program Results'
      Write (nout,*)

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

!     Fix the SORDER = 1, so QUAS(1:N,:)
      sorder = 1

!     Read in the generator to use
      Read (nin,*) genid

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

      If (genid==4) Then
        liref = 407
      Else
        liref = 32*idim + 7
      End If

!     Because we are calling G05YRF, IREF needs to be IDIM elements
!     bigger than the minimum length
      liref = liref + idim

      Allocate (iref(liref),xmean(idim),std(idim))

!     Read in the parameters for the distribution
      Read (nin,*) xmean(1:idim)
      Read (nin,*) std(1:idim)

!     Read in the dimensions that we require
      Read (nin,*) fdim, ldim

      rdim = ldim - fdim + 1
      ldquas = n
      Allocate (quas(ldquas,rdim))

!     Initialize the generator
      ifail = 0
      Call g05ylf(genid,idim,iref,liref,iskip,ifail)

!     Generate N quasi-random variates for dimensions FDIM to LDIM
      ifail = 0
      Call g05yrf(sorder,n,xmean,std,fdim,ldim,quas,ldquas,iref,ifail)

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

!     Display the first DN variates
      Write (nout,*)
      Write (nout,99999) 'First ', dn, ' variates for dimensions ', fdim,      &
        ' to ', ldim
      Write (nout,99997)(i,i=fdim,ldim)
      Do i = 1, n
        Write (nout,99998) i, quas(i,:)
      End Do

99999 Format (A,I0,A,I0,A,I0)
99998 Format (I5,5X,100(1X,F8.4))
99997 Format (10X,100(2X,I4,3X))
    End Program g05yrfe