Program g13asfe

!     G13ASF Example Program Text

!     Mark 25 Release. NAG Copyright 2014.

!     .. Use Statements ..
      Use nag_library, Only: g13aff, g13asf, nag_wp, x04abf
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: iset = 1, nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: c, chi, s, siglev
      Integer                          :: idf, ifail, ires, ishow, itc, kfc,   &
                                          kpiv, ldcm, ldrcm, liw, lwork, m, n, &
                                          nadv, ndf, nit, npar, nppc, nst, nx, &
                                          pp, qp
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: cm(:,:), par(:), r(:), rcm(:,:),     &
                                          sd(:), st(:), v(:), work(:), x(:)
      Integer                          :: isf(4), mr(7)
      Integer, Allocatable             :: iw(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: max
!     .. Executable Statements ..
      Write (nout,*) 'G13ASF Example Program Results'
      Write (nout,*)
      Flush (nout)

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

!     Read in problem size
      Read (nin,*) nx, kfc, c

!     Read in the orders
      Read (nin,*) mr(1:7)

!     Calculate NPAR and various array sizes
      npar = mr(1) + mr(3) + mr(4) + mr(6)
      nppc = npar + kfc
      ldcm = nppc
      pp = mr(1) + mr(4)*mr(7)
      qp = mr(3) + mr(6)*mr(7)
      ires = 15*qp + 11*nx + 13*nppc + 8*pp + 12 + 2*(qp+nppc)**2

      Allocate (par(npar),x(nx),sd(nppc),cm(ldcm,nppc),st(nx),v(ires))

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

!     Read in initial values
      Read (nin,*) par(1:npar)

!     Read in control parameters
      Read (nin,*) kpiv, nit

!     Set the advisory channel to NOUT for monitoring information
      If (kpiv/=0) Then
        nadv = nout
        Call x04abf(iset,nadv)
      End If

!     Fit ARIMA model
      ifail = -1
      Call g13aff(mr,par,npar,c,kfc,x,nx,s,ndf,sd,nppc,cm,ldcm,st,nst,kpiv, &
        nit,itc,isf,v,ires,n,ifail)
      If (ifail/=0) Then
        If (ifail/=9) Then
          Go To 100
        End If
      End If

!     Read in parameters for G13ASF
      Read (nin,*) m, ishow

      ldrcm = m
      liw = max(mr(1),mr(3),mr(4),mr(6))
      lwork = npar*(n+npar+1) + liw*max(mr(7),1) + m
      Allocate (r(m),rcm(ldrcm,m),iw(liw),work(lwork))

!     Set the advisory channel to NOUT for monitoring information
!     if it has not been set previously
      If (ishow/=0 .And. kpiv==0) Then
        nadv = nout
        Call x04abf(iset,nadv)
      End If

!     Perform diagnostic checks
      ifail = 0
      Call g13asf(n,v,mr,m,par,npar,ishow,r,rcm,ldrcm,chi,idf,siglev,iw,liw, &
        work,lwork,ifail)

100   Continue

    End Program g13asfe