Program g13mgfe
!     G13MGF Example Program Text

!     Mark 26.1 Release. NAG Copyright 2016.

!     .. Use Statements ..
      Use nag_library, Only: g13mgf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: p, tau
      Integer                          :: ftype, i, ierr, ifail, lrcomm,       &
                                          lsinit, m1, m2, nb, pn
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: ma(:), rcomm(:), sinit(:), t(:),     &
                                          wma(:)
      Integer                          :: inter(2)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: repeat
!     .. Executable Statements ..
      Write (nout,*) 'G13MGF Example Program Results'
      Write (nout,*)

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

!     Read in the number of iterations required
      Read (nin,*) m1, m2

!     Read in the transformation function, its parameter, the interpolation
!     method to use and the decay parameter tau
      Read (nin,*) ftype, p, inter(1:2), tau

!     Read in the initial values
      If (ftype==3 .Or. ftype==5) Then
        lsinit = 2*m2 + 3
      Else
        lsinit = m2 + 2
      End If
      Allocate (sinit(lsinit))
      Read (nin,*) sinit(1:lsinit)

!     Print some titles
      Write (nout,99997) 'Time', 'MA'
      Write (nout,99998) repeat('-',32)

      lrcomm = 20 + 2*m2
      Allocate (rcomm(lrcomm))

!     Loop over each block of data
      pn = 0
      Do
!       Read in the number of observations in this block
        Read (nin,*,Iostat=ierr) nb
        If (ierr/=0) Then
          Exit
        End If

!       Allocate MA, T and WMA to the required size
        Allocate (ma(nb),t(nb),wma(nb))

!       Read in the data for this block
        Do i = 1, nb
          Read (nin,*) t(i), ma(i)
        End Do

!       Update the moving average operator for this block of data
!       G13MGF overwrites the input data
        ifail = 0
        Call g13mgf(nb,ma,t,tau,m1,m2,sinit,inter,ftype,p,pn,wma,rcomm,lrcomm, &
          ifail)

!       Display the results for this block of data
        Write (nout,99999)(pn-nb+i,t(i),ma(i),i=1,nb)
        Write (nout,*)

        Deallocate (t,ma,wma)
      End Do

99999 Format (1X,I3,4X,F10.1,4X,F10.3)
99998 Format (1X,A)
99997 Format (14X,A,10X,A)
    End Program g13mgfe