Program g05yjfe

!     G05YJF Example Program Text

!     Mark 26.1 Release. NAG Copyright 2017.

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

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

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

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

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

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

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

!     Generate N values for the normal distribution
      ifail = 0
      Call g05yjf(xmean,std,n,quas,iref,ifail)

!     Display results
      Write (nout,99999)(quas(i,1:idim),i=1,n)

99999 Format (1X,4F10.4)
    End Program g05yjfe