Program g13acfe
! G13ACF Example Program Text
! Mark 26.2 Release. NAG Copyright 2017.
! .. Use Statements ..
Use nag_library, Only: g13acf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Integer :: i, ifail, nk, nl, nvl
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: ar(:), p(:), r(:), v(:)
! .. Executable Statements ..
Write (nout,*) 'G13ACF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read in the problem size
Read (nin,*) nk, nl
Allocate (ar(nl),p(nl),r(nk),v(nl))
! Read in data
Read (nin,*)(r(i),i=1,nk)
! Calculate partial ACF
ifail = -1
Call g13acf(r,nk,nl,p,v,ar,nvl,ifail)
If (ifail/=0) Then
If (ifail==3) Then
Write (nout,99999) ' Only', nvl, 'valid sets were generated'
Write (nout,*)
Else
Go To 100
End If
End If
! Display results
Write (nout,*) 'Lag Partial Predictor error Autoregressive'
Write (nout,*) ' autocorrn variance ratio' // ' parameter'
Write (nout,*)
Write (nout,99998)(i,p(i),v(i),ar(i),i=1,nvl)
100 Continue
99999 Format (1X,A,I2,A)
99998 Format (1X,I2,F9.3,F16.3,F14.3)
End Program g13acfe