Example description
    Program g01dafe

!     G01DAF Example Program Text

!     Mark 27.0 Release. NAG Copyright 2019.

!     .. Use Statements ..
      Use nag_library, Only: g01daf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: errest, etol
      Integer                          :: ifail, iw, n
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: pp(:), work(:)
!     .. Executable Statements ..
      Write (nout,*) 'G01DAF Example Program Results'
      Write (nout,*)

!     Set the problem size
      n = 15
      etol = 0.001E0_nag_wp

      iw = 3*n/2
      Allocate (pp(n),work(iw))

!     Compute the normal scores
      ifail = 0
      Call g01daf(n,pp,etol,errest,work,iw,ifail)

!     Display results
      Write (nout,99999) 'Set size = ', n
      Write (nout,99998) 'Error tolerance (input) = ', etol
      Write (nout,99998) 'Error estimate (output) = ', errest
      Write (nout,*) 'Normal scores'
      Write (nout,99997) pp(1:n)

99999 Format (1X,A,I2)
99998 Format (1X,A,E13.3)
99997 Format (10X,5F10.3)
    End Program g01dafe