Example description
    Program g01hdfe

!      G01HDF Example Program Text

!     Mark 26.2 Release. NAG Copyright 2017.

!     .. Use Statements ..
      Use nag_library, Only: g01hdf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: epsabs, epsrel, errest, nu, prob
      Integer                          :: fmax, i, ifail, iscov, ldrc, n,      &
                                          nsampl, numsub
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: a(:), b(:), delta(:), rc(:,:)
      Character (1), Allocatable       :: tail(:)
!     .. Executable Statements ..
      Write (nout,*) 'G01HDF Example Program Results'
      Write (nout,*)

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

      Read (nin,*) n, iscov

      ldrc = n

      numsub = 200
      nsampl = 8
      fmax = 25000
      epsabs = 0.0E0_nag_wp
      epsrel = 1.0E-3_nag_wp

      Allocate (tail(n),a(n),b(n),delta(n),rc(ldrc,n))

d_lp: Do
        ifail = 0

        Read (nin,*,Iostat=ifail)
        If (ifail==0) Then
          Read (nin,*,Iostat=ifail) nu
          If (ifail/=0) Then
            Exit d_lp
          End If
        Else
          Exit d_lp
        End If
        Read (nin,*) tail(1:n)
        Read (nin,*) a(1:n)
        Read (nin,*) b(1:n)
        Read (nin,*) delta(1:n)
        Read (nin,*)(rc(i,1:n),i=1,n)

!       Calculate probability
        ifail = 0
        prob = g01hdf(n,tail,a,b,nu,delta,iscov,rc,ldrc,epsabs,epsrel,numsub,  &
          nsampl,fmax,errest,ifail)

        Write (nout,99999) 'Probability:   ', prob
        Write (nout,99998) 'Error estimate:', errest
        Write (nout,*)
      End Do d_lp

99999 Format (2X,A24,E24.8)
99998 Format (2X,A24,E24.2)
    End Program g01hdfe