Program g13fgfe

!     G13FGF Example Program Text

!     Mark 26.1 Release. NAG Copyright 2016.

!     .. Use Statements ..
      Use nag_library, Only: g13fgf, g13fhf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: hp, lgf, tol
      Integer                          :: i, ifail, ip, iq, l, ldcovr, ldx,    &
                                          lwork, maxit, mn, npar, nreg, nt,    &
                                          num
      Logical                          :: copts, tdist
      Character (1)                    :: dist
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: covr(:,:), et(:), fht(:), ht(:),     &
                                          sc(:), se(:), theta(:), work(:),     &
                                          x(:,:), yt(:)
!     .. Executable Statements ..
      Write (nout,*) 'G13FGF Example Program Results'
      Write (nout,*)

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

!     Read in the problem size
      Read (nin,*) num, mn, nreg

      ldx = num
      Allocate (yt(num),x(ldx,nreg))

!     Read in the series
      Read (nin,*) yt(1:num)

!     Read in the exogenous variables
      If (nreg>0) Then
        Read (nin,*)(x(i,1:nreg),i=1,num)
      End If

!     Read in details of the model to fit
      Read (nin,*) dist, ip, iq

!     Read in control parameters
      Read (nin,*) copts, maxit, tol

!     Calculate NPAR
      npar = 1 + 2*iq + ip + mn + nreg
      If (dist=='T' .Or. dist=='t') Then
        npar = npar + 1
        tdist = .True.
      Else
        tdist = .False.
      End If

      ldcovr = npar
      lwork = (nreg+3)*num + npar + 403
      Allocate (theta(npar),se(npar),sc(npar),covr(ldcovr,npar),et(num),       &
        ht(num),work(lwork))

!     Read in initial values
!     alpha_0
      Read (nin,*) theta(1)
      l = 2
!     alpha_i and psi_i
      If (iq>0) Then
        Read (nin,*) theta(l:(l+iq-1))
        l = l + iq
        Read (nin,*) theta(l:(l+iq-1))
        l = l + iq
      End If
!     beta_i
      If (ip>0) Then
        Read (nin,*) theta(l:(l+ip-1))
        l = l + ip
      End If
!     degrees of freedom
      If (tdist) Then
        Read (nin,*) theta(l)
        l = l + 1
      End If
!     mean
      If (mn==1) Then
        Read (nin,*) theta(l)
        l = l + 1
      End If
!     Regression parameters and pre-observed conditional variance
      If (.Not. copts) Then
        Read (nin,*) theta(l:(l+nreg-1))
        Read (nin,*) hp
      End If

!     Fit the GARCH model
      ifail = -1
      Call g13fgf(dist,yt,x,ldx,num,ip,iq,nreg,mn,npar,theta,se,sc,covr,       &
        ldcovr,hp,et,ht,lgf,copts,maxit,tol,work,lwork,ifail)
      If (ifail/=0) Then
        If (ifail/=5 .And. ifail/=6) Then
          Go To 100
        End If
      End If

!     Read in forecast horizon
      Read (nin,*) nt

      Allocate (fht(nt))

!     Calculate the volatility forecast
      ifail = 0
      Call g13fhf(num,nt,ip,iq,theta,fht,ht,et,ifail)

!     Output the results
      Write (nout,*) '               Parameter        Standard'
      Write (nout,*) '               estimates         errors'
!     Output the coefficient alpha_0
      Write (nout,99999) 'Alpha', 0, theta(1), se(1)
      l = 2
!     Output the coefficients alpha_i and psi_i
      If (iq>0) Then
        Write (nout,99999)('Alpha',i-1,theta(i),se(i),i=l,l+iq-1)
        l = l + iq
        Write (nout,99999)('  Psi',i-l+1,theta(i),se(i),i=l,l+iq-1)
        l = l + iq
      End If
      Write (nout,*)
!     Output the coefficients beta_j
      If (ip>0) Then
        Write (nout,99999)(' Beta',i-l+1,theta(i),se(i),i=l,l+ip-1)
        l = l + ip
        Write (nout,*)
      End If
!     Output the estimated degrees of freedom, df
      If (dist=='T') Then
        Write (nout,99998) '    DF', theta(l), se(l)
        l = l + 1
        Write (nout,*)
      End If
!     Output the estimated mean term, b_0
      If (mn==1) Then
        Write (nout,99999) '    B', 0, theta(l), se(l)
        l = l + 1
      End If
!     Output the estimated linear regression coefficients, b_i
      If (nreg>0) Then
        Write (nout,99999)('    B',i-l+1,theta(i),se(i),i=l,l+nreg-1)
      End If

!     Display the volatility forecast
      Write (nout,*)
      Write (nout,99997) 'Volatility forecast = ', fht(nt)
      Write (nout,*)

100   Continue
99999 Format (1X,A,I0,1X,2F16.2)
99998 Format (1X,A,1X,2F16.2)
99997 Format (1X,A,F12.2)
    End Program g13fgfe