Program g10bbfe
!     G10BBF Example Program Text

!     Mark 26.1 Release. NAG Copyright 2016.

!     .. Use Statements ..
      Use nag_library, Only: g10bbf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: shi, slo, window
      Integer                          :: fcall, i, ifail, n, ns, wtype
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: rcomm(:), smooth(:), t(:), x(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: min
!     .. Executable Statements ..
      Write (nout,*) 'G10BBF Example Program Results'
      Write (nout,*)

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

!     Read in density estimation information
      Read (nin,*) wtype, window, slo, shi, ns

!     Read in the size of the dataset
      Read (nin,*) n

      Allocate (smooth(ns),t(ns),rcomm(ns+20),x(n))

!     Only calling the routine once
      fcall = 1

!     Read in data
      Read (nin,*) x(1:n)

!     Perform kernel density estimation
      ifail = 0
      Call g10bbf(n,x,wtype,window,slo,shi,ns,smooth,t,fcall,rcomm,ifail)

!     Display the results
      Write (nout,99998) 'Window Width Used = ', window
      Write (nout,99997) 'Interval = (', slo, ',', shi, ')'
      Write (nout,*)
      Write (nout,99999) 'First ', min(20,ns), ' output values:'
      Write (nout,*)
      Write (nout,*) '      Time        Density'
      Write (nout,*) '      Point       Estimate'
      Write (nout,*) ' ---------------------------'
      Do i = 1, min(20,ns)
        Write (nout,99996) t(i), smooth(i)
      End Do

99999 Format (A,I0,A)
99998 Format (A,E11.4)
99997 Format (A,E11.4,A,E11.4,A)
99996 Format (1X,E13.4,1X,E13.4)
    End Program g10bbfe