NAG Library Manual, Mark 28.5
Interfaces:  FL   CL   CPP   AD 

NAG FL Interface Introduction
Example description
    Program g13mefe
!     G13MEF Example Program Text

!     Mark 28.5 Release. NAG Copyright 2022.

!     .. Use Statements ..
      Use nag_library, Only: g13mef, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: tau
      Integer                          :: i, ierr, ifail, lrcomm, m, nb, pn
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: iema(:), rcomm(:), sinit(:), t(:)
      Integer                          :: inter(2)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: repeat
!     .. Executable Statements ..
      Write (nout,*) 'G13MEF Example Program Results'
      Write (nout,*)

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

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

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

!     Read in the initial values
      Allocate (sinit(m+2))
      Read (nin,*) sinit(1:m+2)

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

      lrcomm = 20 + m
      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 IEMA and T to the required size
        Allocate (iema(nb),t(nb))

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

!       Update the iterated EMA for this block of data
!       G13MEF overwrites the input data with the iterated EMA
        ifail = 0
        Call g13mef(nb,iema,t,tau,m,sinit,inter,pn,rcomm,lrcomm,ifail)

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

        Deallocate (t,iema)
      End Do

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