Program g13awfe
! G13AWF Example Program Text
! Mark 29.2 Release. NAG Copyright 2023.
! .. Use Statements ..
Use nag_library, Only: g01ewf, g13awf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: pvalue, ts
Integer :: ifail, method, n, nsamp, p, type
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: y(:)
Integer :: state(1)
! .. Executable Statements ..
Write (nout,*) 'G13AWF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read in the problem size, test type, order of the AR process
Read (nin,*) n, type, p
! Allocate memory
Allocate (y(n))
! Read in the time series
Read (nin,*) y(1:n)
! Calculate the Dickey-Fuller test statistic
ifail = 0
ts = g13awf(type,p,n,y,ifail)
! Get the associated p-value using the look-up method
method = 1
ifail = -1
pvalue = g01ewf(method,type,n,ts,nsamp,state,ifail)
If (ifail==0 .Or. ifail==201) Then
! Display the results
Write (nout,'(A,F6.3)') 'Dickey-Fuller test statistic = ', ts
Write (nout,'(A,F6.3)') 'associated p-value = ', pvalue
End If
End Program g13awfe