Program g13dlfe
! G13DLF Example Program Text
! Mark 26.1 Release. NAG Copyright 2016.
! .. Use Statements ..
Use nag_library, Only: g13dlf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Integer :: d, i, ifail, k, kmax, n, nd, tddelta
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: delta(:,:), w(:,:), work(:), z(:,:)
Integer, Allocatable :: id(:)
Character (1), Allocatable :: tr(:)
! .. Intrinsic Procedures ..
Intrinsic :: max, maxval
! .. Executable Statements ..
Write (nout,*) 'G13DLF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read in problem size
Read (nin,*) k, n
Allocate (id(k))
! Read in differencing
Read (nin,*) id(1:k)
d = maxval(id(1:k))
tddelta = max(d,1)
nd = n - d
kmax = k
Allocate (z(kmax,n),tr(k),delta(kmax,tddelta),w(kmax,nd),work(k*n))
! Read in series and the transformation flag
Read (nin,*)(z(i,1:n),i=1,k)
Read (nin,*) tr(1:k)
! If required, read in delta
If (d>0) Then
Read (nin,*)(delta(i,1:id(i)),i=1,k)
End If
! Difference and / or transform series
ifail = 0
Call g13dlf(k,n,z,kmax,tr,id,delta,w,nd,work,ifail)
! Display results
Write (nout,*) ' Transformed/Differenced series'
Write (nout,*) ' ------------------------------'
Do i = 1, k
Write (nout,*)
Write (nout,99999) ' Series ', i
Write (nout,*) ' -----------'
Write (nout,*)
Write (nout,99998) ' Number of differenced values = ', nd
Write (nout,*)
Write (nout,99997) w(i,1:nd)
End Do
99999 Format (1X,A,I2)
99998 Format (1X,A,I6)
99997 Format (1X,8F9.3)
End Program g13dlfe