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

NAG FL Interface Introduction
Example description
    Program g13bdfe

!     G13BDF Example Program Text

!     Mark 28.7 Release. NAG Copyright 2022.

!     .. Use Statements ..
      Use nag_library, Only: g13bdf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: r0, s
      Integer                          :: ifail, iwa, nl, nwds
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: r(:), wa(:), wds(:)
      Integer                          :: isf(2), nna(3)
!     .. Executable Statements ..
      Write (nout,*) 'G13BDF Example Program Results'
      Write (nout,*)

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

!     Read in problem size and cross-correlation at lag 0
      Read (nin,*) nl, r0

      Allocate (r(nl))

!     Read in rest of cross-correlations
      Read (nin,*) r(1:nl)

!     Read in transfer function model orders
      Read (nin,*) nna(1:3)

!     Read in standard deviation ratio
      Read (nin,*) s

      nwds = nna(2) + nna(3) + 1
      iwa = 0
      Allocate (wa(iwa),wds(nwds))

!     Calculate parameter estimates
      ifail = 0
      Call g13bdf(r0,r,nl,nna,s,nwds,wa,iwa,wds,isf,ifail)

!     Display results
      Write (nout,99999) 'Success/failure indicator', isf(1), isf(2)
      Write (nout,*)
      Write (nout,99999) 'Transfer function model B, Q, P =', nna(1:3)
      Write (nout,*)
      Write (nout,*) 'Parameter initial estimates'
      Write (nout,99998) wds(1:nwds)

99999 Format (1X,A,3I4)
99998 Format (1X,4F10.4)
    End Program g13bdfe